bloodhound-0.15.0.1: 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.V1.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

newtype BH m a Source #

Constructors

BH 

Fields

Instances

MonadTrans BH Source # 

Methods

lift :: Monad m => m a -> BH m a #

MonadWriter w m => MonadWriter w (BH m) Source # 

Methods

writer :: (a, w) -> BH m a #

tell :: w -> BH m () #

listen :: BH m a -> BH m (a, w) #

pass :: BH m (a, w -> w) -> BH m a #

MonadState s m => MonadState s (BH m) Source # 

Methods

get :: BH m s #

put :: s -> BH m () #

state :: (s -> (a, s)) -> BH m a #

MonadReader r m => MonadReader r (BH m) Source # 

Methods

ask :: BH m r #

local :: (r -> r) -> BH m a -> BH m a #

reader :: (r -> a) -> BH m a #

MonadError e m => MonadError e (BH m) Source # 

Methods

throwError :: e -> BH m a #

catchError :: BH m a -> (e -> BH m a) -> BH m a #

Monad m => Monad (BH m) Source # 

Methods

(>>=) :: BH m a -> (a -> BH m b) -> BH m b #

(>>) :: BH m a -> BH m b -> BH m b #

return :: a -> BH m a #

fail :: String -> BH m a #

Functor m => Functor (BH m) Source # 

Methods

fmap :: (a -> b) -> BH m a -> BH m b #

(<$) :: a -> BH m b -> BH m a #

MonadFix m => MonadFix (BH m) Source # 

Methods

mfix :: (a -> BH m a) -> BH m a #

Applicative m => Applicative (BH m) Source # 

Methods

pure :: a -> BH m a #

(<*>) :: BH m (a -> b) -> BH m a -> BH m b #

liftA2 :: (a -> b -> c) -> BH m a -> BH m b -> BH m c #

(*>) :: BH m a -> BH m b -> BH m b #

(<*) :: BH m a -> BH m b -> BH m a #

Alternative m => Alternative (BH m) Source # 

Methods

empty :: BH m a #

(<|>) :: BH m a -> BH m a -> BH m a #

some :: BH m a -> BH m [a] #

many :: BH m a -> BH m [a] #

MonadPlus m => MonadPlus (BH m) Source # 

Methods

mzero :: BH m a #

mplus :: BH m a -> BH m a -> BH m a #

MonadIO m => MonadIO (BH m) Source # 

Methods

liftIO :: IO a -> BH m a #

MonadThrow m => MonadThrow (BH m) Source # 

Methods

throwM :: Exception e => e -> BH m a #

MonadCatch m => MonadCatch (BH m) Source # 

Methods

catch :: Exception e => BH m a -> (e -> BH m a) -> BH m a #

MonadMask m => MonadMask (BH m) Source # 

Methods

mask :: ((forall a. BH m a -> BH m a) -> BH m b) -> BH m b #

uninterruptibleMask :: ((forall a. BH m a -> BH m a) -> BH m b) -> BH m b #

(Functor m, Applicative m, MonadIO m) => MonadBH (BH m) Source # 

Methods

getBHEnv :: BH m BHEnv Source #

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.

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.

Minimal complete definition

getBHEnv

Methods

getBHEnv :: m BHEnv Source #

data Version Source #

Version is embedded in Status

Instances

Eq Version Source # 

Methods

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

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

Read Version Source # 
Show Version Source # 
Generic Version Source # 

Associated Types

type Rep Version :: * -> * #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

ToJSON Version Source # 
FromJSON Version Source # 
type Rep Version Source # 

newtype VersionNumber Source #

Traditional software versioning number

Constructors

VersionNumber 

Instances

Eq VersionNumber Source # 
Ord VersionNumber Source # 
Read VersionNumber Source # 
Show VersionNumber Source # 
Generic VersionNumber Source # 

Associated Types

type Rep VersionNumber :: * -> * #

ToJSON VersionNumber Source # 
FromJSON VersionNumber Source # 
type Rep VersionNumber Source # 
type Rep VersionNumber = D1 * (MetaData "VersionNumber" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "VersionNumber" PrefixI True) (S1 * (MetaSel (Just Symbol "versionNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Version)))

newtype MaybeNA a Source #

Constructors

MaybeNA 

Fields

Instances

Eq a => Eq (MaybeNA a) Source # 

Methods

(==) :: MaybeNA a -> MaybeNA a -> Bool #

(/=) :: MaybeNA a -> MaybeNA a -> Bool #

Show a => Show (MaybeNA a) Source # 

Methods

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

show :: MaybeNA a -> String #

showList :: [MaybeNA a] -> ShowS #

FromJSON a => FromJSON (MaybeNA a) Source # 

newtype BuildHash Source #

Typically a 7 character hex string.

Constructors

BuildHash 

Fields

Instances

Eq BuildHash Source # 
Ord BuildHash Source # 
Read BuildHash Source # 
Show BuildHash Source # 
Generic BuildHash Source # 

Associated Types

type Rep BuildHash :: * -> * #

ToJSON BuildHash Source # 
FromJSON BuildHash Source # 
type Rep BuildHash Source # 
type Rep BuildHash = D1 * (MetaData "BuildHash" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "BuildHash" PrefixI True) (S1 * (MetaSel (Just Symbol "buildHash") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

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

data IndexSettings Source #

IndexSettings is used to configure the shards and replicas when you create an Elasticsearch Index.

http://www.elasticsearch.org/guide/en/elasticsearch/reference/current/indices-create-index.html

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 

Instances

Eq UpdatableIndexSetting Source # 
Show UpdatableIndexSetting Source # 
Generic UpdatableIndexSetting Source # 
ToJSON UpdatableIndexSetting Source # 
FromJSON UpdatableIndexSetting Source # 
type Rep UpdatableIndexSetting Source # 
type Rep UpdatableIndexSetting = D1 * (MetaData "UpdatableIndexSetting" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NumberOfReplicas" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ReplicaCount))) ((:+:) * (C1 * (MetaCons "AutoExpandReplicas" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ReplicaBounds))) (C1 * (MetaCons "BlocksReadOnly" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))))) ((:+:) * ((:+:) * (C1 * (MetaCons "BlocksRead" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) (C1 * (MetaCons "BlocksWrite" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))) ((:+:) * (C1 * (MetaCons "BlocksMetaData" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) (C1 * (MetaCons "RefreshInterval" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "IndexConcurrency" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:+:) * (C1 * (MetaCons "FailOnMergeFailure" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) (C1 * (MetaCons "TranslogFlushThresholdOps" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))) ((:+:) * ((:+:) * (C1 * (MetaCons "TranslogFlushThresholdSize" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes))) (C1 * (MetaCons "TranslogFlushThresholdPeriod" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime)))) ((:+:) * (C1 * (MetaCons "TranslogDisableFlush" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) (C1 * (MetaCons "CacheFilterMaxSize" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bytes)))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CacheFilterExpire" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NominalDiffTime)))) ((:+:) * (C1 * (MetaCons "GatewaySnapshotInterval" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime))) (C1 * (MetaCons "RoutingAllocationInclude" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (NonEmpty NodeAttrFilter)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "RoutingAllocationExclude" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (NonEmpty NodeAttrFilter)))) (C1 * (MetaCons "RoutingAllocationRequire" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (NonEmpty NodeAttrFilter))))) ((:+:) * (C1 * (MetaCons "RoutingAllocationEnable" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * AllocationPolicy))) (C1 * (MetaCons "RoutingAllocationShardsPerNode" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ShardCount)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "RecoveryInitialShards" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InitialShardCount))) ((:+:) * (C1 * (MetaCons "GCDeletes" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime))) (C1 * (MetaCons "TTLDisablePurge" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))))) ((:+:) * ((:+:) * (C1 * (MetaCons "TranslogFSType" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FSType))) (C1 * (MetaCons "IndexCompoundFormat" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CompoundFormat)))) ((:+:) * (C1 * (MetaCons "IndexCompoundOnFlush" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) (C1 * (MetaCons "WarmerEnabled" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))))))))

data IndexSettingsSummary Source #

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

Instances

Eq AllocationPolicy Source # 
Read AllocationPolicy Source # 
Show AllocationPolicy Source # 
Generic AllocationPolicy Source # 
ToJSON AllocationPolicy Source # 
FromJSON AllocationPolicy Source # 
type Rep AllocationPolicy Source # 
type Rep AllocationPolicy = D1 * (MetaData "AllocationPolicy" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "AllocAll" PrefixI False) (U1 *)) (C1 * (MetaCons "AllocPrimaries" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "AllocNewPrimaries" PrefixI False) (U1 *)) (C1 * (MetaCons "AllocNone" PrefixI False) (U1 *))))

data ReplicaBounds Source #

Instances

Eq ReplicaBounds Source # 
Read ReplicaBounds Source # 
Show ReplicaBounds Source # 
Generic ReplicaBounds Source # 

Associated Types

type Rep ReplicaBounds :: * -> * #

ToJSON ReplicaBounds Source # 
FromJSON ReplicaBounds Source # 
type Rep ReplicaBounds Source # 
type Rep ReplicaBounds = D1 * (MetaData "ReplicaBounds" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * (C1 * (MetaCons "ReplicasBounded" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))) ((:+:) * (C1 * (MetaCons "ReplicasLowerBounded" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "ReplicasUnbounded" PrefixI False) (U1 *))))

newtype Bytes Source #

A measure of bytes used for various configurations. You may want to use smart constructors like gigabytes for larger values.

>>> gigabytes 9
Bytes 9000000000
>>> megabytes 9
Bytes 9000000
>>> kilobytes 9
Bytes 9000

Constructors

Bytes Int 

Instances

Eq Bytes Source # 

Methods

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

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

Ord Bytes Source # 

Methods

compare :: Bytes -> Bytes -> Ordering #

(<) :: Bytes -> Bytes -> Bool #

(<=) :: Bytes -> Bytes -> Bool #

(>) :: Bytes -> Bytes -> Bool #

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

max :: Bytes -> Bytes -> Bytes #

min :: Bytes -> Bytes -> Bytes #

Read Bytes Source # 
Show Bytes Source # 

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

Generic Bytes Source # 

Associated Types

type Rep Bytes :: * -> * #

Methods

from :: Bytes -> Rep Bytes x #

to :: Rep Bytes x -> Bytes #

ToJSON Bytes Source # 
FromJSON Bytes Source # 
type Rep Bytes Source # 
type Rep Bytes = D1 * (MetaData "Bytes" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "Bytes" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))

data FSType Source #

Constructors

FSSimple 
FSBuffered 

Instances

Eq FSType Source # 

Methods

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

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

Ord FSType Source # 
Read FSType Source # 
Show FSType Source # 
Generic FSType Source # 

Associated Types

type Rep FSType :: * -> * #

Methods

from :: FSType -> Rep FSType x #

to :: Rep FSType x -> FSType #

ToJSON FSType Source # 
FromJSON FSType Source # 
type Rep FSType Source # 
type Rep FSType = D1 * (MetaData "FSType" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * (C1 * (MetaCons "FSSimple" PrefixI False) (U1 *)) (C1 * (MetaCons "FSBuffered" PrefixI False) (U1 *)))

data InitialShardCount Source #

Instances

Eq InitialShardCount Source # 
Read InitialShardCount Source # 
Show InitialShardCount Source # 
Generic InitialShardCount Source # 
ToJSON InitialShardCount Source # 
FromJSON InitialShardCount Source # 
type Rep InitialShardCount Source # 
type Rep InitialShardCount = D1 * (MetaData "InitialShardCount" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "QuorumShards" PrefixI False) (U1 *)) (C1 * (MetaCons "QuorumMinus1Shards" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "FullShards" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FullMinus1Shards" PrefixI False) (U1 *)) (C1 * (MetaCons "ExplicitShards" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))))

data NodeAttrFilter Source #

Instances

Eq NodeAttrFilter Source # 
Ord NodeAttrFilter Source # 
Read NodeAttrFilter Source # 
Show NodeAttrFilter Source # 
Generic NodeAttrFilter Source # 

Associated Types

type Rep NodeAttrFilter :: * -> * #

type Rep NodeAttrFilter Source # 
type Rep NodeAttrFilter = D1 * (MetaData "NodeAttrFilter" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodeAttrFilter" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeAttrFilterName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeAttrName)) (S1 * (MetaSel (Just Symbol "nodeAttrFilterValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (NonEmpty Text)))))

data CompoundFormat Source #

Constructors

CompoundFileFormat Bool 
MergeSegmentVsTotalIndex Double

percentage between 0 and 1 where 0 is false, 1 is true

Instances

Eq CompoundFormat Source # 
Read CompoundFormat Source # 
Show CompoundFormat Source # 
Generic CompoundFormat Source # 

Associated Types

type Rep CompoundFormat :: * -> * #

ToJSON CompoundFormat Source # 
FromJSON CompoundFormat Source # 
type Rep CompoundFormat Source # 
type Rep CompoundFormat = D1 * (MetaData "CompoundFormat" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * (C1 * (MetaCons "CompoundFileFormat" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) (C1 * (MetaCons "MergeSegmentVsTotalIndex" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double))))

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 

Instances

Eq Server Source # 

Methods

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

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

Show Server Source # 
Generic Server Source # 

Associated Types

type Rep Server :: * -> * #

Methods

from :: Server -> Rep Server x #

to :: Rep Server x -> Server #

FromJSON Server Source # 
type Rep Server Source # 
type Rep Server = D1 * (MetaData "Server" "Database.V1.Bloodhound.Types.Internal" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "Server" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * 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

Eq a => Eq (EsResult a) Source # 

Methods

(==) :: EsResult a -> EsResult a -> Bool #

(/=) :: EsResult a -> EsResult a -> Bool #

Read a => Read (EsResult a) Source # 
Show a => Show (EsResult a) Source # 

Methods

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

show :: EsResult a -> String #

showList :: [EsResult a] -> ShowS #

Generic (EsResult a) Source # 

Associated Types

type Rep (EsResult a) :: * -> * #

Methods

from :: EsResult a -> Rep (EsResult a) x #

to :: Rep (EsResult a) x -> EsResult a #

FromJSON a => FromJSON (EsResult a) Source # 
type Rep (EsResult a) Source # 

data EsResultFound a Source #

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

Constructors

EsResultFound 

Fields

Instances

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 

Instances

Eq EsError Source # 

Methods

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

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

Read EsError Source # 
Show EsError Source # 
Generic EsError Source # 

Associated Types

type Rep EsError :: * -> * #

Methods

from :: EsError -> Rep EsError x #

to :: Rep EsError x -> EsError #

FromJSON EsError Source # 
type Rep EsError Source # 
type Rep EsError = D1 * (MetaData "EsError" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "EsError" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "errorStatus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "errorMessage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))

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 IndexAliasAction Source #

Instances

Eq IndexAliasAction Source # 
Read IndexAliasAction Source # 
Show IndexAliasAction Source # 
Generic IndexAliasAction Source # 
ToJSON IndexAliasAction Source # 
type Rep IndexAliasAction Source # 

data IndexAliasCreate Source #

Instances

Eq IndexAliasCreate Source # 
Read IndexAliasCreate Source # 
Show IndexAliasCreate Source # 
Generic IndexAliasCreate Source # 
ToJSON IndexAliasCreate Source # 
FromJSON IndexAliasCreate Source # 
type Rep IndexAliasCreate Source # 
type Rep IndexAliasCreate = D1 * (MetaData "IndexAliasCreate" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "IndexAliasCreate" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "aliasCreateRouting") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AliasRouting))) (S1 * (MetaSel (Just Symbol "aliasCreateFilter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Filter)))))

data AliasRouting Source #

Instances

Eq AliasRouting Source # 
Read AliasRouting Source # 
Show AliasRouting Source # 
Generic AliasRouting Source # 

Associated Types

type Rep AliasRouting :: * -> * #

ToJSON AliasRouting Source # 
FromJSON AliasRouting Source # 
type Rep AliasRouting Source # 

newtype SearchAliasRouting Source #

newtype IndexAliasRouting Source #

data DocVersion Source #

DocVersion is an integer version number for a document between 1 and 9.2e+18 used for .

Instances

Bounded DocVersion Source # 
Enum DocVersion Source # 
Eq DocVersion Source # 
Ord DocVersion Source # 
Read DocVersion Source # 
Show DocVersion Source # 
Generic DocVersion Source # 

Associated Types

type Rep DocVersion :: * -> * #

ToJSON DocVersion Source # 
FromJSON DocVersion Source # 
type Rep DocVersion Source # 
type Rep DocVersion = D1 * (MetaData "DocVersion" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "DocVersion" PrefixI True) (S1 * (MetaSel (Just Symbol "docVersionNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))

newtype ExternalDocVersion Source #

ExternalDocVersion is a convenience wrapper if your code uses its own version numbers instead of ones from ES.

Instances

Bounded ExternalDocVersion Source # 
Enum ExternalDocVersion Source # 
Eq ExternalDocVersion Source # 
Ord ExternalDocVersion Source # 
Read ExternalDocVersion Source # 
Show ExternalDocVersion Source # 
Generic ExternalDocVersion Source # 
ToJSON ExternalDocVersion Source # 
type Rep ExternalDocVersion Source # 
type Rep ExternalDocVersion = D1 * (MetaData "ExternalDocVersion" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "ExternalDocVersion" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DocVersion)))

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.

Instances

Eq VersionControl Source # 
Ord VersionControl Source # 
Read VersionControl Source # 
Show VersionControl Source # 
Generic VersionControl Source # 

Associated Types

type Rep VersionControl :: * -> * #

type Rep VersionControl Source # 

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 Query Source #

Instances

Eq Query Source # 

Methods

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

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

Read Query Source # 
Show Query Source # 

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Generic Query Source # 

Associated Types

type Rep Query :: * -> * #

Methods

from :: Query -> Rep Query x #

to :: Rep Query x -> Query #

ToJSON Query Source # 
FromJSON Query Source # 
type Rep Query Source # 
type Rep Query = D1 * (MetaData "Query" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "TermQuery" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Term)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Boost))))) ((:+:) * (C1 * (MetaCons "TermsQuery" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (NonEmpty Text))))) (C1 * (MetaCons "QueryMatchQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MatchQuery))))) ((:+:) * ((:+:) * (C1 * (MetaCons "QueryMultiMatchQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MultiMatchQuery))) (C1 * (MetaCons "QueryBoolQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * BoolQuery)))) ((:+:) * (C1 * (MetaCons "QueryBoostingQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * BoostingQuery))) (C1 * (MetaCons "QueryCommonTermsQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CommonTermsQuery)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "ConstantScoreFilter" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Filter)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Boost)))) ((:+:) * (C1 * (MetaCons "ConstantScoreQuery" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Query)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Boost)))) (C1 * (MetaCons "QueryDisMaxQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DisMaxQuery))))) ((:+:) * ((:+:) * (C1 * (MetaCons "QueryFilteredQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilteredQuery))) (C1 * (MetaCons "QueryFuzzyLikeThisQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FuzzyLikeThisQuery)))) ((:+:) * (C1 * (MetaCons "QueryFuzzyLikeFieldQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FuzzyLikeFieldQuery))) (C1 * (MetaCons "QueryFuzzyQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FuzzyQuery))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "QueryHasChildQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * HasChildQuery))) ((:+:) * (C1 * (MetaCons "QueryHasParentQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * HasParentQuery))) (C1 * (MetaCons "IdsQuery" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MappingName)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [DocId])))))) ((:+:) * ((:+:) * (C1 * (MetaCons "QueryIndicesQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * IndicesQuery))) (C1 * (MetaCons "MatchAllQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Boost))))) ((:+:) * (C1 * (MetaCons "QueryMoreLikeThisQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MoreLikeThisQuery))) (C1 * (MetaCons "QueryMoreLikeThisFieldQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MoreLikeThisFieldQuery)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "QueryNestedQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NestedQuery))) ((:+:) * (C1 * (MetaCons "QueryPrefixQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PrefixQuery))) (C1 * (MetaCons "QueryQueryStringQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * QueryStringQuery))))) ((:+:) * ((:+:) * (C1 * (MetaCons "QuerySimpleQueryStringQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * SimpleQueryStringQuery))) (C1 * (MetaCons "QueryRangeQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * RangeQuery)))) ((:+:) * (C1 * (MetaCons "QueryRegexpQuery" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * RegexpQuery))) (C1 * (MetaCons "QueryTemplateQueryInline" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TemplateQueryInline))))))))

data Search Source #

Constructors

Search 

Instances

Eq Search Source # 

Methods

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

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

Read Search Source # 
Show Search Source # 
Generic Search Source # 

Associated Types

type Rep Search :: * -> * #

Methods

from :: Search -> Rep Search x #

to :: Rep Search x -> Search #

ToJSON Search Source # 
type Rep Search Source # 
type Rep Search = D1 * (MetaData "Search" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "Search" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "queryBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Query))) ((:*:) * (S1 * (MetaSel (Just Symbol "filterBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Filter))) (S1 * (MetaSel (Just Symbol "sortBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Sort))))) ((:*:) * (S1 * (MetaSel (Just Symbol "aggBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Aggregations))) ((:*:) * (S1 * (MetaSel (Just Symbol "highlight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Highlights))) (S1 * (MetaSel (Just Symbol "trackSortScores") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TrackSortScores))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "from") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * From)) ((:*:) * (S1 * (MetaSel (Just Symbol "size") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Size)) (S1 * (MetaSel (Just Symbol "searchType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * SearchType)))) ((:*:) * (S1 * (MetaSel (Just Symbol "fields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe [FieldName]))) ((:*:) * (S1 * (MetaSel (Just Symbol "source") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Source))) (S1 * (MetaSel (Just Symbol "suggestBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Suggest))))))))

data SearchType Source #

Instances

Eq SearchType Source # 
Read SearchType Source # 
Show SearchType Source # 
Generic SearchType Source # 

Associated Types

type Rep SearchType :: * -> * #

type Rep SearchType Source # 
type Rep SearchType = D1 * (MetaData "SearchType" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "SearchTypeQueryThenFetch" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SearchTypeDfsQueryThenFetch" PrefixI False) (U1 *)) (C1 * (MetaCons "SearchTypeCount" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "SearchTypeScan" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SearchTypeQueryAndFetch" PrefixI False) (U1 *)) (C1 * (MetaCons "SearchTypeDfsQueryAndFetch" PrefixI False) (U1 *)))))

data SearchResult a Source #

Constructors

SearchResult 

Fields

Instances

Eq a => Eq (SearchResult a) Source # 
Read a => Read (SearchResult a) Source # 
Show a => Show (SearchResult a) Source # 
Generic (SearchResult a) Source # 

Associated Types

type Rep (SearchResult a) :: * -> * #

Methods

from :: SearchResult a -> Rep (SearchResult a) x #

to :: Rep (SearchResult a) x -> SearchResult a #

FromJSON a => FromJSON (SearchResult a) Source # 
type Rep (SearchResult a) Source # 

newtype ScrollId Source #

Constructors

ScrollId Text 

data SearchHits a Source #

Constructors

SearchHits 

Fields

Instances

Eq a => Eq (SearchHits a) Source # 

Methods

(==) :: SearchHits a -> SearchHits a -> Bool #

(/=) :: SearchHits a -> SearchHits a -> Bool #

Read a => Read (SearchHits a) Source # 
Show a => Show (SearchHits a) Source # 
Generic (SearchHits a) Source # 

Associated Types

type Rep (SearchHits a) :: * -> * #

Methods

from :: SearchHits a -> Rep (SearchHits a) x #

to :: Rep (SearchHits a) x -> SearchHits a #

Semigroup (SearchHits a) Source # 
Monoid (SearchHits a) Source # 
FromJSON a => FromJSON (SearchHits a) Source # 
type Rep (SearchHits a) Source # 
type Rep (SearchHits a) = D1 * (MetaData "SearchHits" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "SearchHits" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "hitsTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "maxScore") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Score)) (S1 * (MetaSel (Just Symbol "hits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Hit a])))))

newtype From Source #

Constructors

From Int 

Instances

Eq From Source # 

Methods

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

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

Read From Source # 
Show From Source # 

Methods

showsPrec :: Int -> From -> ShowS #

show :: From -> String #

showList :: [From] -> ShowS #

Generic From Source # 

Associated Types

type Rep From :: * -> * #

Methods

from :: From -> Rep From x #

to :: Rep From x -> From #

ToJSON From Source # 
type Rep From Source # 
type Rep From = D1 * (MetaData "From" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "From" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))

newtype Size Source #

Constructors

Size Int 

Instances

Eq Size Source # 

Methods

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

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

Read Size Source # 
Show Size Source # 

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Generic Size Source # 

Associated Types

type Rep Size :: * -> * #

Methods

from :: Size -> Rep Size x #

to :: Rep Size x -> Size #

ToJSON Size Source # 
FromJSON Size Source # 
type Rep Size Source # 
type Rep Size = D1 * (MetaData "Size" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "Size" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))

data PatternOrPatterns Source #

data Include Source #

Constructors

Include [Pattern] 

Instances

Eq Include Source # 

Methods

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

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

Read Include Source # 
Show Include Source # 
Generic Include Source # 

Associated Types

type Rep Include :: * -> * #

Methods

from :: Include -> Rep Include x #

to :: Rep Include x -> Include #

ToJSON Include Source # 
type Rep Include Source # 
type Rep Include = D1 * (MetaData "Include" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "Include" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Pattern])))

data Exclude Source #

Constructors

Exclude [Pattern] 

Instances

Eq Exclude Source # 

Methods

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

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

Read Exclude Source # 
Show Exclude Source # 
Generic Exclude Source # 

Associated Types

type Rep Exclude :: * -> * #

Methods

from :: Exclude -> Rep Exclude x #

to :: Rep Exclude x -> Exclude #

ToJSON Exclude Source # 
type Rep Exclude Source # 
type Rep Exclude = D1 * (MetaData "Exclude" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "Exclude" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Pattern])))

newtype Pattern Source #

Constructors

Pattern Text 

Instances

Eq Pattern Source # 

Methods

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

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

Read Pattern Source # 
Show Pattern Source # 
Generic Pattern Source # 

Associated Types

type Rep Pattern :: * -> * #

Methods

from :: Pattern -> Rep Pattern x #

to :: Rep Pattern x -> Pattern #

ToJSON Pattern Source # 
type Rep Pattern Source # 
type Rep Pattern = D1 * (MetaData "Pattern" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "Pattern" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data Hit a Source #

Instances

Eq a => Eq (Hit a) Source # 

Methods

(==) :: Hit a -> Hit a -> Bool #

(/=) :: Hit a -> Hit a -> Bool #

Read a => Read (Hit a) Source # 
Show a => Show (Hit a) Source # 

Methods

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

show :: Hit a -> String #

showList :: [Hit a] -> ShowS #

Generic (Hit a) Source # 

Associated Types

type Rep (Hit a) :: * -> * #

Methods

from :: Hit a -> Rep (Hit a) x #

to :: Rep (Hit a) x -> Hit a #

FromJSON a => FromJSON (Hit a) Source # 

Methods

parseJSON :: Value -> Parser (Hit a) #

parseJSONList :: Value -> Parser [Hit a] #

type Rep (Hit a) Source # 

data Filter Source #

class Monoid a => Seminearring a where Source #

Minimal complete definition

(<||>)

Methods

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

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

data BoolMatch Source #

Instances

Eq BoolMatch Source # 
Read BoolMatch Source # 
Show BoolMatch Source # 
Generic BoolMatch Source # 

Associated Types

type Rep BoolMatch :: * -> * #

ToJSON BoolMatch Source # 
FromJSON BoolMatch Source # 
type Rep BoolMatch Source # 

data Term Source #

Constructors

Term 

Fields

Instances

Eq Term Source # 

Methods

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

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

Read Term Source # 
Show Term Source # 

Methods

showsPrec :: Int -> Term -> ShowS #

show :: Term -> String #

showList :: [Term] -> ShowS #

Generic Term Source # 

Associated Types

type Rep Term :: * -> * #

Methods

from :: Term -> Rep Term x #

to :: Rep Term x -> Term #

ToJSON Term Source # 
FromJSON Term Source # 
type Rep Term Source # 
type Rep Term = D1 * (MetaData "Term" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "Term" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "termField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "termValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))

data GeoBoundingBoxConstraint Source #

Instances

Eq GeoBoundingBoxConstraint Source # 
Read GeoBoundingBoxConstraint Source # 
Show GeoBoundingBoxConstraint Source # 
Generic GeoBoundingBoxConstraint Source # 
ToJSON GeoBoundingBoxConstraint Source # 
FromJSON GeoBoundingBoxConstraint Source # 
type Rep GeoBoundingBoxConstraint Source # 
type Rep GeoBoundingBoxConstraint = D1 * (MetaData "GeoBoundingBoxConstraint" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "GeoBoundingBoxConstraint" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "geoBBField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FieldName)) (S1 * (MetaSel (Just Symbol "constraintBox") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GeoBoundingBox))) ((:*:) * (S1 * (MetaSel (Just Symbol "bbConstraintcache") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Cache)) (S1 * (MetaSel (Just Symbol "geoType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GeoFilterType)))))

data GeoBoundingBox Source #

Constructors

GeoBoundingBox 

data DistanceUnit Source #

Instances

Eq DistanceUnit Source # 
Read DistanceUnit Source # 
Show DistanceUnit Source # 
Generic DistanceUnit Source # 

Associated Types

type Rep DistanceUnit :: * -> * #

ToJSON DistanceUnit Source # 
FromJSON DistanceUnit Source # 
type Rep DistanceUnit Source # 
type Rep DistanceUnit = D1 * (MetaData "DistanceUnit" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Miles" PrefixI False) (U1 *)) (C1 * (MetaCons "Yards" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Feet" PrefixI False) (U1 *)) (C1 * (MetaCons "Inches" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Kilometers" PrefixI False) (U1 *)) (C1 * (MetaCons "Meters" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Centimeters" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Millimeters" PrefixI False) (U1 *)) (C1 * (MetaCons "NauticalMiles" PrefixI False) (U1 *))))))

data LatLon Source #

Constructors

LatLon 

Fields

data RangeValue Source #

Instances

Eq RangeValue Source # 
Read RangeValue Source # 
Show RangeValue Source # 
Generic RangeValue Source # 

Associated Types

type Rep RangeValue :: * -> * #

FromJSON RangeValue Source # 
type Rep RangeValue Source # 
type Rep RangeValue = D1 * (MetaData "RangeValue" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "RangeDateLte" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LessThanEqD))) (C1 * (MetaCons "RangeDateLt" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LessThanD)))) ((:+:) * (C1 * (MetaCons "RangeDateGte" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GreaterThanEqD))) (C1 * (MetaCons "RangeDateGt" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GreaterThanD))))) ((:+:) * ((:+:) * (C1 * (MetaCons "RangeDateGtLt" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GreaterThanD)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LessThanD)))) (C1 * (MetaCons "RangeDateGteLte" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GreaterThanEqD)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LessThanEqD))))) ((:+:) * (C1 * (MetaCons "RangeDateGteLt" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GreaterThanEqD)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LessThanD)))) (C1 * (MetaCons "RangeDateGtLte" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GreaterThanD)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LessThanEqD))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "RangeDoubleLte" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LessThanEq))) (C1 * (MetaCons "RangeDoubleLt" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LessThan)))) ((:+:) * (C1 * (MetaCons "RangeDoubleGte" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GreaterThanEq))) (C1 * (MetaCons "RangeDoubleGt" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GreaterThan))))) ((:+:) * ((:+:) * (C1 * (MetaCons "RangeDoubleGtLt" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GreaterThan)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LessThan)))) (C1 * (MetaCons "RangeDoubleGteLte" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GreaterThanEq)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LessThanEq))))) ((:+:) * (C1 * (MetaCons "RangeDoubleGteLt" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GreaterThanEq)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LessThan)))) (C1 * (MetaCons "RangeDoubleGtLte" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GreaterThan)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LessThanEq))))))))

newtype LessThan Source #

Constructors

LessThan Double 

Instances

Eq LessThan Source # 
Read LessThan Source # 
Show LessThan Source # 
Generic LessThan Source # 

Associated Types

type Rep LessThan :: * -> * #

Methods

from :: LessThan -> Rep LessThan x #

to :: Rep LessThan x -> LessThan #

type Rep LessThan Source # 
type Rep LessThan = D1 * (MetaData "LessThan" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "LessThan" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)))

newtype LessThanD Source #

Constructors

LessThanD UTCTime 

Instances

newtype Regexp Source #

Constructors

Regexp Text 

Instances

Eq Regexp Source # 

Methods

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

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

Read Regexp Source # 
Show Regexp Source # 
Generic Regexp Source # 

Associated Types

type Rep Regexp :: * -> * #

Methods

from :: Regexp -> Rep Regexp x #

to :: Rep Regexp x -> Regexp #

FromJSON Regexp Source # 
type Rep Regexp Source # 
type Rep Regexp = D1 * (MetaData "Regexp" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "Regexp" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data RegexpFlags Source #

data RegexpFlag Source #

Instances

Eq RegexpFlag Source # 
Read RegexpFlag Source # 
Show RegexpFlag Source # 
Generic RegexpFlag Source # 

Associated Types

type Rep RegexpFlag :: * -> * #

FromJSON RegexpFlag Source # 
type Rep RegexpFlag Source # 
type Rep RegexpFlag = D1 * (MetaData "RegexpFlag" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "AnyString" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Automaton" PrefixI False) (U1 *)) (C1 * (MetaCons "Complement" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "Empty" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Intersection" PrefixI False) (U1 *)) (C1 * (MetaCons "Interval" PrefixI False) (U1 *)))))

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

Instances

Eq Script Source # 

Methods

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

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

Read Script Source # 
Show Script Source # 
Generic Script Source # 

Associated Types

type Rep Script :: * -> * #

Methods

from :: Script -> Rep Script x #

to :: Rep Script x -> Script #

type Rep Script Source # 
type Rep Script = D1 * (MetaData "Script" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "Script" PrefixI True) (S1 * (MetaSel (Just Symbol "scriptText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * 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.

Instances

data NodeSelection Source #

NodeSelection is used for most cluster APIs. See here for more details.

Constructors

LocalNode

Whatever node receives this request

NodeList (NonEmpty NodeSelector) 
AllNodes 

Instances

Eq NodeSelection Source # 
Show NodeSelection Source # 
Generic NodeSelection Source # 

Associated Types

type Rep NodeSelection :: * -> * #

type Rep NodeSelection Source # 
type Rep NodeSelection = D1 * (MetaData "NodeSelection" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * (C1 * (MetaCons "LocalNode" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NodeList" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (NonEmpty NodeSelector)))) (C1 * (MetaCons "AllNodes" PrefixI False) (U1 *))))

data NodeSelector Source #

An exact match or pattern to identify a node. Note that All of these options support wildcarding, so your node name, server, attr name can all contain * characters to be a fuzzy match.

Constructors

NodeByName NodeName 
NodeByFullNodeId FullNodeId 
NodeByHost Server

e.g. 10.0.0.1 or even 10.0.0.*

NodeByAttribute NodeAttrName Text

NodeAttrName can be a pattern, e.g. rack*. The value can too.

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 TemplatePattern Source #

TemplatePattern represents a pattern which is matched against index names

Constructors

TemplatePattern Text 

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 

Instances

Eq DocId Source # 

Methods

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

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

Read DocId Source # 
Show DocId Source # 

Methods

showsPrec :: Int -> DocId -> ShowS #

show :: DocId -> String #

showList :: [DocId] -> ShowS #

Generic DocId Source # 

Associated Types

type Rep DocId :: * -> * #

Methods

from :: DocId -> Rep DocId x #

to :: Rep DocId x -> DocId #

ToJSON DocId Source # 
FromJSON DocId Source # 
type Rep DocId Source # 
type Rep DocId = D1 * (MetaData "DocId" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "DocId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

newtype CacheKey Source #

CacheKey is used in RegexpFilter to key regex caching.

Constructors

CacheKey Text 

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

Instances

Eq BulkOperation Source # 
Read BulkOperation Source # 
Show BulkOperation Source # 
Generic BulkOperation Source # 

Associated Types

type Rep BulkOperation :: * -> * #

type Rep BulkOperation Source # 
type Rep BulkOperation = D1 * (MetaData "BulkOperation" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "BulkIndex" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * IndexName)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MappingName))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DocId)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Value))))) (C1 * (MetaCons "BulkCreate" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * IndexName)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MappingName))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DocId)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Value)))))) ((:+:) * (C1 * (MetaCons "BulkDelete" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * IndexName)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MappingName)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DocId))))) (C1 * (MetaCons "BulkUpdate" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * IndexName)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MappingName))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DocId)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Value)))))))

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 SortMode Source #

Constructors

SortMin 
SortMax 
SortSum 
SortAvg 

Instances

Eq SortMode Source # 
Read SortMode Source # 
Show SortMode Source # 
Generic SortMode Source # 

Associated Types

type Rep SortMode :: * -> * #

Methods

from :: SortMode -> Rep SortMode x #

to :: Rep SortMode x -> SortMode #

ToJSON SortMode Source # 
type Rep SortMode Source # 
type Rep SortMode = D1 * (MetaData "SortMode" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "SortMin" PrefixI False) (U1 *)) (C1 * (MetaCons "SortMax" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "SortSum" PrefixI False) (U1 *)) (C1 * (MetaCons "SortAvg" PrefixI False) (U1 *))))

data SortOrder Source #

Constructors

Ascending 
Descending 

Instances

Eq SortOrder Source # 
Read SortOrder Source # 
Show SortOrder Source # 
Generic SortOrder Source # 

Associated Types

type Rep SortOrder :: * -> * #

ToJSON SortOrder Source # 
type Rep SortOrder Source # 
type Rep SortOrder = D1 * (MetaData "SortOrder" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * (C1 * (MetaCons "Ascending" PrefixI False) (U1 *)) (C1 * (MetaCons "Descending" PrefixI False) (U1 *)))

data SortSpec Source #

The two main kinds of SortSpec are DefaultSortSpec and GeoDistanceSortSpec. The latter takes a SortOrder, GeoPoint, and DistanceUnit to express "nearness" to a single geographical point as a sort specification.

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

data DefaultSort Source #

DefaultSort is usually the kind of SortSpec you'll want. There's a mkSort convenience function for when you want to specify only the most common parameters.

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

Instances

Eq DefaultSort Source # 
Read DefaultSort Source # 
Show DefaultSort Source # 
Generic DefaultSort Source # 

Associated Types

type Rep DefaultSort :: * -> * #

type Rep DefaultSort Source # 

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

Instances

Eq Missing Source # 

Methods

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

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

Read Missing Source # 
Show Missing Source # 
Generic Missing Source # 

Associated Types

type Rep Missing :: * -> * #

Methods

from :: Missing -> Rep Missing x #

to :: Rep Missing x -> Missing #

ToJSON Missing Source # 
type Rep Missing Source # 
type Rep Missing = D1 * (MetaData "Missing" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * (C1 * (MetaCons "LastMissing" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FirstMissing" PrefixI False) (U1 *)) (C1 * (MetaCons "CustomMissing" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))))

newtype Boost Source #

Constructors

Boost Double 

Instances

Eq Boost Source # 

Methods

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

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

Read Boost Source # 
Show Boost Source # 

Methods

showsPrec :: Int -> Boost -> ShowS #

show :: Boost -> String #

showList :: [Boost] -> ShowS #

Generic Boost Source # 

Associated Types

type Rep Boost :: * -> * #

Methods

from :: Boost -> Rep Boost x #

to :: Rep Boost x -> Boost #

ToJSON Boost Source # 
FromJSON Boost Source # 
type Rep Boost Source # 
type Rep Boost = D1 * (MetaData "Boost" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "Boost" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)))

data MatchQuery Source #

Instances

Eq MatchQuery Source # 
Read MatchQuery Source # 
Show MatchQuery Source # 
Generic MatchQuery Source # 

Associated Types

type Rep MatchQuery :: * -> * #

ToJSON MatchQuery Source # 
FromJSON MatchQuery Source # 
type Rep MatchQuery Source # 
type Rep MatchQuery = D1 * (MetaData "MatchQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "MatchQuery" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "matchQueryField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FieldName)) (S1 * (MetaSel (Just Symbol "matchQueryQueryString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * QueryString))) ((:*:) * (S1 * (MetaSel (Just Symbol "matchQueryOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * BooleanOperator)) ((:*:) * (S1 * (MetaSel (Just Symbol "matchQueryZeroTerms") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ZeroTermsQuery)) (S1 * (MetaSel (Just Symbol "matchQueryCutoffFrequency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CutoffFrequency)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "matchQueryMatchType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MatchQueryType))) (S1 * (MetaSel (Just Symbol "matchQueryAnalyzer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Analyzer)))) ((:*:) * (S1 * (MetaSel (Just Symbol "matchQueryMaxExpansions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MaxExpansions))) ((:*:) * (S1 * (MetaSel (Just Symbol "matchQueryLenient") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Lenient))) (S1 * (MetaSel (Just Symbol "matchQueryBoost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Boost))))))))

data MultiMatchQuery Source #

Instances

Eq MultiMatchQuery Source # 
Read MultiMatchQuery Source # 
Show MultiMatchQuery Source # 
Generic MultiMatchQuery Source # 
ToJSON MultiMatchQuery Source # 
FromJSON MultiMatchQuery Source # 
type Rep MultiMatchQuery Source # 
type Rep MultiMatchQuery = D1 * (MetaData "MultiMatchQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "MultiMatchQuery" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "multiMatchQueryFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FieldName])) (S1 * (MetaSel (Just Symbol "multiMatchQueryString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * QueryString))) ((:*:) * (S1 * (MetaSel (Just Symbol "multiMatchQueryOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * BooleanOperator)) ((:*:) * (S1 * (MetaSel (Just Symbol "multiMatchQueryZeroTerms") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ZeroTermsQuery)) (S1 * (MetaSel (Just Symbol "multiMatchQueryTiebreaker") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Tiebreaker)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "multiMatchQueryType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MultiMatchQueryType))) (S1 * (MetaSel (Just Symbol "multiMatchQueryCutoffFrequency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CutoffFrequency)))) ((:*:) * (S1 * (MetaSel (Just Symbol "multiMatchQueryAnalyzer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Analyzer))) ((:*:) * (S1 * (MetaSel (Just Symbol "multiMatchQueryMaxExpansions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MaxExpansions))) (S1 * (MetaSel (Just Symbol "multiMatchQueryLenient") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Lenient))))))))

data BoolQuery Source #

Instances

Eq BoolQuery Source # 
Read BoolQuery Source # 
Show BoolQuery Source # 
Generic BoolQuery Source # 

Associated Types

type Rep BoolQuery :: * -> * #

ToJSON BoolQuery Source # 
FromJSON BoolQuery Source # 
type Rep BoolQuery Source # 
type Rep BoolQuery = D1 * (MetaData "BoolQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "BoolQuery" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "boolQueryMustMatch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Query])) ((:*:) * (S1 * (MetaSel (Just Symbol "boolQueryMustNotMatch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Query])) (S1 * (MetaSel (Just Symbol "boolQueryShouldMatch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Query])))) ((:*:) * (S1 * (MetaSel (Just Symbol "boolQueryMinimumShouldMatch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MinimumMatch))) ((:*:) * (S1 * (MetaSel (Just Symbol "boolQueryBoost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Boost))) (S1 * (MetaSel (Just Symbol "boolQueryDisableCoord") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe DisableCoord)))))))

data BoostingQuery Source #

Instances

Eq BoostingQuery Source # 
Read BoostingQuery Source # 
Show BoostingQuery Source # 
Generic BoostingQuery Source # 

Associated Types

type Rep BoostingQuery :: * -> * #

ToJSON BoostingQuery Source # 
FromJSON BoostingQuery Source # 
type Rep BoostingQuery Source # 
type Rep BoostingQuery = D1 * (MetaData "BoostingQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "BoostingQuery" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "positiveQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Query)) ((:*:) * (S1 * (MetaSel (Just Symbol "negativeQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Query)) (S1 * (MetaSel (Just Symbol "negativeBoost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Boost)))))

data CommonTermsQuery Source #

Instances

Eq CommonTermsQuery Source # 
Read CommonTermsQuery Source # 
Show CommonTermsQuery Source # 
Generic CommonTermsQuery Source # 
ToJSON CommonTermsQuery Source # 
FromJSON CommonTermsQuery Source # 
type Rep CommonTermsQuery Source # 

data DisMaxQuery Source #

Instances

Eq DisMaxQuery Source # 
Read DisMaxQuery Source # 
Show DisMaxQuery Source # 
Generic DisMaxQuery Source # 

Associated Types

type Rep DisMaxQuery :: * -> * #

ToJSON DisMaxQuery Source # 
FromJSON DisMaxQuery Source # 
type Rep DisMaxQuery Source # 
type Rep DisMaxQuery = D1 * (MetaData "DisMaxQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "DisMaxQuery" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "disMaxQueries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Query])) ((:*:) * (S1 * (MetaSel (Just Symbol "disMaxTiebreaker") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Tiebreaker)) (S1 * (MetaSel (Just Symbol "disMaxBoost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Boost))))))

data FilteredQuery Source #

data FuzzyLikeThisQuery Source #

Instances

Eq FuzzyLikeThisQuery Source # 
Read FuzzyLikeThisQuery Source # 
Show FuzzyLikeThisQuery Source # 
Generic FuzzyLikeThisQuery Source # 
ToJSON FuzzyLikeThisQuery Source # 
FromJSON FuzzyLikeThisQuery Source # 
type Rep FuzzyLikeThisQuery Source # 

data FuzzyLikeFieldQuery Source #

Instances

Eq FuzzyLikeFieldQuery Source # 
Read FuzzyLikeFieldQuery Source # 
Show FuzzyLikeFieldQuery Source # 
Generic FuzzyLikeFieldQuery Source # 
ToJSON FuzzyLikeFieldQuery Source # 
FromJSON FuzzyLikeFieldQuery Source # 
type Rep FuzzyLikeFieldQuery Source # 
type Rep FuzzyLikeFieldQuery = D1 * (MetaData "FuzzyLikeFieldQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "FuzzyLikeFieldQuery" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fuzzyLikeField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FieldName)) (S1 * (MetaSel (Just Symbol "fuzzyLikeFieldText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "fuzzyLikeFieldMaxQueryTerms") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MaxQueryTerms)) (S1 * (MetaSel (Just Symbol "fuzzyLikeFieldIgnoreTermFrequency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * IgnoreTermFrequency)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fuzzyLikeFieldFuzziness") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Fuzziness)) (S1 * (MetaSel (Just Symbol "fuzzyLikeFieldPrefixLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PrefixLength))) ((:*:) * (S1 * (MetaSel (Just Symbol "fuzzyLikeFieldBoost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Boost)) (S1 * (MetaSel (Just Symbol "fuzzyLikeFieldAnalyzer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Analyzer)))))))

data FuzzyQuery Source #

Instances

Eq FuzzyQuery Source # 
Read FuzzyQuery Source # 
Show FuzzyQuery Source # 
Generic FuzzyQuery Source # 

Associated Types

type Rep FuzzyQuery :: * -> * #

ToJSON FuzzyQuery Source # 
FromJSON FuzzyQuery Source # 
type Rep FuzzyQuery Source # 
type Rep FuzzyQuery = D1 * (MetaData "FuzzyQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "FuzzyQuery" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fuzzyQueryField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FieldName)) ((:*:) * (S1 * (MetaSel (Just Symbol "fuzzyQueryValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "fuzzyQueryPrefixLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PrefixLength)))) ((:*:) * (S1 * (MetaSel (Just Symbol "fuzzyQueryMaxExpansions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MaxExpansions)) ((:*:) * (S1 * (MetaSel (Just Symbol "fuzzyQueryFuzziness") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Fuzziness)) (S1 * (MetaSel (Just Symbol "fuzzyQueryBoost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Boost)))))))

data HasChildQuery Source #

Instances

Eq HasChildQuery Source # 
Read HasChildQuery Source # 
Show HasChildQuery Source # 
Generic HasChildQuery Source # 

Associated Types

type Rep HasChildQuery :: * -> * #

ToJSON HasChildQuery Source # 
FromJSON HasChildQuery Source # 
type Rep HasChildQuery Source # 
type Rep HasChildQuery = D1 * (MetaData "HasChildQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "HasChildQuery" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "hasChildQueryType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TypeName)) ((:*:) * (S1 * (MetaSel (Just Symbol "hasChildQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Query)) (S1 * (MetaSel (Just Symbol "hasChildQueryScoreType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe ScoreType))))))

data HasParentQuery Source #

Instances

Eq HasParentQuery Source # 
Read HasParentQuery Source # 
Show HasParentQuery Source # 
Generic HasParentQuery Source # 

Associated Types

type Rep HasParentQuery :: * -> * #

ToJSON HasParentQuery Source # 
FromJSON HasParentQuery Source # 
type Rep HasParentQuery Source # 
type Rep HasParentQuery = D1 * (MetaData "HasParentQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "HasParentQuery" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "hasParentQueryType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TypeName)) ((:*:) * (S1 * (MetaSel (Just Symbol "hasParentQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Query)) (S1 * (MetaSel (Just Symbol "hasParentQueryScoreType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe ScoreType))))))

data IndicesQuery Source #

Instances

Eq IndicesQuery Source # 
Read IndicesQuery Source # 
Show IndicesQuery Source # 
Generic IndicesQuery Source # 

Associated Types

type Rep IndicesQuery :: * -> * #

ToJSON IndicesQuery Source # 
FromJSON IndicesQuery Source # 
type Rep IndicesQuery Source # 
type Rep IndicesQuery = D1 * (MetaData "IndicesQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "IndicesQuery" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "indicesQueryIndices") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [IndexName])) ((:*:) * (S1 * (MetaSel (Just Symbol "indicesQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Query)) (S1 * (MetaSel (Just Symbol "indicesQueryNoMatch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Query))))))

data MoreLikeThisQuery Source #

Instances

Eq MoreLikeThisQuery Source # 
Read MoreLikeThisQuery Source # 
Show MoreLikeThisQuery Source # 
Generic MoreLikeThisQuery Source # 
ToJSON MoreLikeThisQuery Source # 
FromJSON MoreLikeThisQuery Source # 
type Rep MoreLikeThisQuery Source # 
type Rep MoreLikeThisQuery = D1 * (MetaData "MoreLikeThisQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "MoreLikeThisQuery" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (NonEmpty FieldName)))) (S1 * (MetaSel (Just Symbol "moreLikeThisPercentMatch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PercentMatch))))) ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisMinimumTermFreq") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MinimumTermFrequency))) ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisMaxQueryTerms") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MaxQueryTerms))) (S1 * (MetaSel (Just Symbol "moreLikeThisStopWords") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (NonEmpty StopWord))))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisMinDocFrequency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MinDocFrequency))) ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisMaxDocFrequency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MaxDocFrequency))) (S1 * (MetaSel (Just Symbol "moreLikeThisMinWordLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MinWordLength))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisMaxWordLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MaxWordLength))) (S1 * (MetaSel (Just Symbol "moreLikeThisBoostTerms") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BoostTerms)))) ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisBoost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Boost))) (S1 * (MetaSel (Just Symbol "moreLikeThisAnalyzer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Analyzer))))))))

data MoreLikeThisFieldQuery Source #

Instances

Eq MoreLikeThisFieldQuery Source # 
Read MoreLikeThisFieldQuery Source # 
Show MoreLikeThisFieldQuery Source # 
Generic MoreLikeThisFieldQuery Source # 
ToJSON MoreLikeThisFieldQuery Source # 
FromJSON MoreLikeThisFieldQuery Source # 
type Rep MoreLikeThisFieldQuery Source # 
type Rep MoreLikeThisFieldQuery = D1 * (MetaData "MoreLikeThisFieldQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "MoreLikeThisFieldQuery" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisFieldText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisFieldFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FieldName)) (S1 * (MetaSel (Just Symbol "moreLikeThisFieldPercentMatch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PercentMatch))))) ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisFieldMinimumTermFreq") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MinimumTermFrequency))) ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisFieldMaxQueryTerms") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MaxQueryTerms))) (S1 * (MetaSel (Just Symbol "moreLikeThisFieldStopWords") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (NonEmpty StopWord))))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisFieldMinDocFrequency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MinDocFrequency))) ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisFieldMaxDocFrequency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MaxDocFrequency))) (S1 * (MetaSel (Just Symbol "moreLikeThisFieldMinWordLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MinWordLength))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisFieldMaxWordLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MaxWordLength))) (S1 * (MetaSel (Just Symbol "moreLikeThisFieldBoostTerms") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BoostTerms)))) ((:*:) * (S1 * (MetaSel (Just Symbol "moreLikeThisFieldBoost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Boost))) (S1 * (MetaSel (Just Symbol "moreLikeThisFieldAnalyzer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Analyzer))))))))

data NestedQuery Source #

Instances

Eq NestedQuery Source # 
Read NestedQuery Source # 
Show NestedQuery Source # 
Generic NestedQuery Source # 

Associated Types

type Rep NestedQuery :: * -> * #

ToJSON NestedQuery Source # 
FromJSON NestedQuery Source # 
type Rep NestedQuery Source # 
type Rep NestedQuery = D1 * (MetaData "NestedQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NestedQuery" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "nestedQueryPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * QueryPath)) ((:*:) * (S1 * (MetaSel (Just Symbol "nestedQueryScoreType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ScoreType)) (S1 * (MetaSel (Just Symbol "nestedQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Query)))))

data PrefixQuery Source #

Instances

Eq PrefixQuery Source # 
Read PrefixQuery Source # 
Show PrefixQuery Source # 
Generic PrefixQuery Source # 

Associated Types

type Rep PrefixQuery :: * -> * #

ToJSON PrefixQuery Source # 
FromJSON PrefixQuery Source # 
type Rep PrefixQuery Source # 
type Rep PrefixQuery = D1 * (MetaData "PrefixQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "PrefixQuery" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "prefixQueryField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FieldName)) ((:*:) * (S1 * (MetaSel (Just Symbol "prefixQueryPrefixValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "prefixQueryBoost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Boost))))))

data QueryStringQuery Source #

Instances

Eq QueryStringQuery Source # 
Read QueryStringQuery Source # 
Show QueryStringQuery Source # 
Generic QueryStringQuery Source # 
ToJSON QueryStringQuery Source # 
FromJSON QueryStringQuery Source # 
type Rep QueryStringQuery Source # 
type Rep QueryStringQuery = D1 * (MetaData "QueryStringQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "QueryStringQuery" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "queryStringQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * QueryString)) (S1 * (MetaSel (Just Symbol "queryStringDefaultField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FieldName)))) ((:*:) * (S1 * (MetaSel (Just Symbol "queryStringOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BooleanOperator))) (S1 * (MetaSel (Just Symbol "queryStringAnalyzer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Analyzer))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "queryStringAllowLeadingWildcard") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AllowLeadingWildcard))) (S1 * (MetaSel (Just Symbol "queryStringLowercaseExpanded") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LowercaseExpanded)))) ((:*:) * (S1 * (MetaSel (Just Symbol "queryStringEnablePositionIncrements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe EnablePositionIncrements))) (S1 * (MetaSel (Just Symbol "queryStringFuzzyMaxExpansions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MaxExpansions)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "queryStringFuzziness") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Fuzziness))) (S1 * (MetaSel (Just Symbol "queryStringFuzzyPrefixLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PrefixLength)))) ((:*:) * (S1 * (MetaSel (Just Symbol "queryStringPhraseSlop") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PhraseSlop))) (S1 * (MetaSel (Just Symbol "queryStringBoost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Boost))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "queryStringAnalyzeWildcard") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AnalyzeWildcard))) (S1 * (MetaSel (Just Symbol "queryStringGeneratePhraseQueries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe GeneratePhraseQueries)))) ((:*:) * (S1 * (MetaSel (Just Symbol "queryStringMinimumShouldMatch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe MinimumMatch))) ((:*:) * (S1 * (MetaSel (Just Symbol "queryStringLenient") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Lenient))) (S1 * (MetaSel (Just Symbol "queryStringLocale") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Locale)))))))))

data SimpleQueryStringQuery Source #

Instances

Eq SimpleQueryStringQuery Source # 
Read SimpleQueryStringQuery Source # 
Show SimpleQueryStringQuery Source # 
Generic SimpleQueryStringQuery Source # 
ToJSON SimpleQueryStringQuery Source # 
FromJSON SimpleQueryStringQuery Source # 
type Rep SimpleQueryStringQuery Source # 
type Rep SimpleQueryStringQuery = D1 * (MetaData "SimpleQueryStringQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "SimpleQueryStringQuery" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "simpleQueryStringQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * QueryString)) ((:*:) * (S1 * (MetaSel (Just Symbol "simpleQueryStringField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FieldOrFields))) (S1 * (MetaSel (Just Symbol "simpleQueryStringOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BooleanOperator))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "simpleQueryStringAnalyzer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Analyzer))) (S1 * (MetaSel (Just Symbol "simpleQueryStringFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (NonEmpty SimpleQueryFlag))))) ((:*:) * (S1 * (MetaSel (Just Symbol "simpleQueryStringLowercaseExpanded") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LowercaseExpanded))) (S1 * (MetaSel (Just Symbol "simpleQueryStringLocale") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Locale)))))))

data RangeQuery Source #

data RegexpQuery Source #

Instances

Eq RegexpQuery Source # 
Read RegexpQuery Source # 
Show RegexpQuery Source # 
Generic RegexpQuery Source # 

Associated Types

type Rep RegexpQuery :: * -> * #

ToJSON RegexpQuery Source # 
FromJSON RegexpQuery Source # 
type Rep RegexpQuery Source # 
type Rep RegexpQuery = D1 * (MetaData "RegexpQuery" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "RegexpQuery" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "regexpQueryField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FieldName)) (S1 * (MetaSel (Just Symbol "regexpQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Regexp))) ((:*:) * (S1 * (MetaSel (Just Symbol "regexpQueryFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * RegexpFlags)) (S1 * (MetaSel (Just Symbol "regexpQueryBoost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Boost))))))

data TemplateQueryInline Source #

Instances

Eq TemplateQueryInline Source # 
Read TemplateQueryInline Source # 
Show TemplateQueryInline Source # 
Generic TemplateQueryInline Source # 
ToJSON TemplateQueryInline Source # 
FromJSON TemplateQueryInline Source # 
type Rep TemplateQueryInline Source # 
type Rep TemplateQueryInline = D1 * (MetaData "TemplateQueryInline" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "TemplateQueryInline" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "inline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Query)) (S1 * (MetaSel (Just Symbol "params") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TemplateQueryKeyValuePairs))))

newtype TemplateQueryKeyValuePairs Source #

Constructors

TemplateQueryKeyValuePairs (HashMap TemplateQueryKey TemplateQueryValue) 

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 

data MultiMatchQueryType Source #

Instances

Eq MultiMatchQueryType Source # 
Read MultiMatchQueryType Source # 
Show MultiMatchQueryType Source # 
Generic MultiMatchQueryType Source # 
ToJSON MultiMatchQueryType Source # 
FromJSON MultiMatchQueryType Source # 
type Rep MultiMatchQueryType Source # 
type Rep MultiMatchQueryType = D1 * (MetaData "MultiMatchQueryType" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "MultiMatchBestFields" PrefixI False) (U1 *)) (C1 * (MetaCons "MultiMatchMostFields" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "MultiMatchCrossFields" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "MultiMatchPhrase" PrefixI False) (U1 *)) (C1 * (MetaCons "MultiMatchPhrasePrefix" PrefixI False) (U1 *)))))

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 

data CommonMinimumMatch Source #

Instances

Eq CommonMinimumMatch Source # 
Read CommonMinimumMatch Source # 
Show CommonMinimumMatch Source # 
Generic CommonMinimumMatch Source # 
ToJSON CommonMinimumMatch Source # 
FromJSON CommonMinimumMatch Source # 
type Rep CommonMinimumMatch Source # 
type Rep CommonMinimumMatch = D1 * (MetaData "CommonMinimumMatch" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * (C1 * (MetaCons "CommonMinimumMatchHighLow" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MinimumMatchHighLow))) (C1 * (MetaCons "CommonMinimumMatch" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MinimumMatch))))

newtype IgnoreTermFrequency Source #

Instances

Eq IgnoreTermFrequency Source # 
Read IgnoreTermFrequency Source # 
Show IgnoreTermFrequency Source # 
Generic IgnoreTermFrequency Source # 
ToJSON IgnoreTermFrequency Source # 
FromJSON IgnoreTermFrequency Source # 
type Rep IgnoreTermFrequency Source # 
type Rep IgnoreTermFrequency = D1 * (MetaData "IgnoreTermFrequency" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "IgnoreTermFrequency" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))

data ScoreType Source #

Instances

Eq ScoreType Source # 
Read ScoreType Source # 
Show ScoreType Source # 
Generic ScoreType Source # 

Associated Types

type Rep ScoreType :: * -> * #

ToJSON ScoreType Source # 
FromJSON ScoreType Source # 
type Rep ScoreType Source # 
type Rep ScoreType = D1 * (MetaData "ScoreType" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ScoreTypeMax" PrefixI False) (U1 *)) (C1 * (MetaCons "ScoreTypeSum" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ScoreTypeAvg" PrefixI False) (U1 *)) (C1 * (MetaCons "ScoreTypeNone" PrefixI False) (U1 *))))

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 

newtype MinimumTermFrequency Source #

Instances

Eq MinimumTermFrequency Source # 
Read MinimumTermFrequency Source # 
Show MinimumTermFrequency Source # 
Generic MinimumTermFrequency Source # 
ToJSON MinimumTermFrequency Source # 
FromJSON MinimumTermFrequency Source # 
type Rep MinimumTermFrequency Source # 
type Rep MinimumTermFrequency = D1 * (MetaData "MinimumTermFrequency" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "MinimumTermFrequency" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * 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 

Instances

Eq Mapping Source # 

Methods

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

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

Read Mapping Source # 
Show Mapping Source # 
Generic Mapping Source # 

Associated Types

type Rep Mapping :: * -> * #

Methods

from :: Mapping -> Rep Mapping x #

to :: Rep Mapping x -> Mapping #

type Rep Mapping Source # 
type Rep Mapping = D1 * (MetaData "Mapping" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "Mapping" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "typeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TypeName)) (S1 * (MetaSel (Just Symbol "mappingFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [MappingField]))))

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.

Instances

Eq AllowLeadingWildcard Source # 
Read AllowLeadingWildcard Source # 
Show AllowLeadingWildcard Source # 
Generic AllowLeadingWildcard Source # 
ToJSON AllowLeadingWildcard Source # 
FromJSON AllowLeadingWildcard Source # 
type Rep AllowLeadingWildcard Source # 
type Rep AllowLeadingWildcard = D1 * (MetaData "AllowLeadingWildcard" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "AllowLeadingWildcard" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))

newtype LowercaseExpanded Source #

Constructors

LowercaseExpanded Bool 

newtype GeneratePhraseQueries Source #

GeneratePhraseQueries defaults to false.

Instances

Eq GeneratePhraseQueries Source # 
Read GeneratePhraseQueries Source # 
Show GeneratePhraseQueries Source # 
Generic GeneratePhraseQueries Source # 
ToJSON GeneratePhraseQueries Source # 
FromJSON GeneratePhraseQueries Source # 
type Rep GeneratePhraseQueries Source # 
type Rep GeneratePhraseQueries = D1 * (MetaData "GeneratePhraseQueries" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "GeneratePhraseQueries" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))

newtype Locale Source #

Locale is used for string conversions - defaults to ROOT.

Constructors

Locale Text 

Instances

newtype AnalyzeWildcard Source #

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

Constructors

AnalyzeWildcard Bool 

newtype EnablePositionIncrements Source #

Instances

Eq EnablePositionIncrements Source # 
Read EnablePositionIncrements Source # 
Show EnablePositionIncrements Source # 
Generic EnablePositionIncrements Source # 
ToJSON EnablePositionIncrements Source # 
FromJSON EnablePositionIncrements Source # 
type Rep EnablePositionIncrements Source # 
type Rep EnablePositionIncrements = D1 * (MetaData "EnablePositionIncrements" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "EnablePositionIncrements" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))

data SimpleQueryFlag Source #

Instances

Eq SimpleQueryFlag Source # 
Read SimpleQueryFlag Source # 
Show SimpleQueryFlag Source # 
Generic SimpleQueryFlag Source # 
ToJSON SimpleQueryFlag Source # 
FromJSON SimpleQueryFlag Source # 
type Rep SimpleQueryFlag Source # 
type Rep SimpleQueryFlag = D1 * (MetaData "SimpleQueryFlag" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "SimpleQueryAll" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SimpleQueryNone" PrefixI False) (U1 *)) (C1 * (MetaCons "SimpleQueryAnd" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "SimpleQueryOr" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SimpleQueryPrefix" PrefixI False) (U1 *)) (C1 * (MetaCons "SimpleQueryPhrase" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "SimpleQueryPrecedence" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SimpleQueryEscape" PrefixI False) (U1 *)) (C1 * (MetaCons "SimpleQueryWhitespace" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "SimpleQueryFuzzy" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SimpleQueryNear" PrefixI False) (U1 *)) (C1 * (MetaCons "SimpleQuerySlop" PrefixI False) (U1 *))))))

data FieldOrFields Source #

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

Since: 2.1

Monoid ()

Since: 2.1

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid ByteString 
Monoid ByteString 
Monoid Builder 
Monoid Series 
Monoid More 

Methods

mempty :: More #

mappend :: More -> More -> More #

mconcat :: [More] -> More #

Monoid All

Since: 2.1

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any

Since: 2.1

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid ShortByteString 
Monoid IntSet 
Monoid CookieJar

Since 1.9

Monoid RequestBody 
Monoid Filter # 
Monoid [a]

Since: 2.1

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

mconcat :: [[a]] -> [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 used to be no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Since: 2.1

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (IO a)

Since: 4.9.0.0

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

Monoid (IResult a) 

Methods

mempty :: IResult a #

mappend :: IResult a -> IResult a -> IResult a #

mconcat :: [IResult a] -> IResult a #

Monoid (Result a) 

Methods

mempty :: Result a #

mappend :: Result a -> Result a -> Result a #

mconcat :: [Result a] -> Result a #

Monoid (Parser a) 

Methods

mempty :: Parser a #

mappend :: Parser a -> Parser a -> Parser a #

mconcat :: [Parser a] -> Parser a #

(Ord a, Bounded a) => Monoid (Min a)

Since: 4.9.0.0

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

(Ord a, Bounded a) => Monoid (Max a)

Since: 4.9.0.0

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Monoid m => Monoid (WrappedMonoid m)

Since: 4.9.0.0

Semigroup a => Monoid (Option a)

Since: 4.9.0.0

Methods

mempty :: Option a #

mappend :: Option a -> Option a -> Option a #

mconcat :: [Option a] -> Option a #

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Monoid a => Monoid (Dual a)

Since: 2.1

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a)

Since: 2.1

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Sum a)

Since: 2.1

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Num a => Monoid (Product a)

Since: 2.1

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Monoid (First a)

Since: 2.1

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a)

Since: 2.1

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Monoid s => Monoid (CI s) 

Methods

mempty :: CI s #

mappend :: CI s -> CI s -> CI s #

mconcat :: [CI s] -> CI s #

Monoid (IntMap a) 

Methods

mempty :: IntMap a #

mappend :: IntMap a -> IntMap a -> IntMap a #

mconcat :: [IntMap a] -> IntMap a #

Monoid (Seq a) 

Methods

mempty :: Seq a #

mappend :: Seq a -> Seq a -> Seq a #

mconcat :: [Seq a] -> Seq a #

Ord a => Monoid (Set a) 

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

mconcat :: [Set a] -> Set a #

Monoid (DList a) 

Methods

mempty :: DList a #

mappend :: DList a -> DList a -> DList a #

mconcat :: [DList a] -> DList a #

Monoid (Array a) 

Methods

mempty :: Array a #

mappend :: Array a -> Array a -> Array a #

mconcat :: [Array a] -> Array a #

(Hashable a, Eq a) => Monoid (HashSet a) 

Methods

mempty :: HashSet a #

mappend :: HashSet a -> HashSet a -> HashSet a #

mconcat :: [HashSet a] -> HashSet a #

Storable a => Monoid (Vector a) 

Methods

mempty :: Vector a #

mappend :: Vector a -> Vector a -> Vector a #

mconcat :: [Vector a] -> Vector a #

Prim a => Monoid (Vector a) 

Methods

mempty :: Vector a #

mappend :: Vector a -> Vector a -> Vector a #

mconcat :: [Vector a] -> Vector a #

Monoid (Vector a) 

Methods

mempty :: Vector a #

mappend :: Vector a -> Vector a -> Vector a #

mconcat :: [Vector a] -> Vector a #

Monoid (SearchHits a) # 
Monoid (SearchHits a) # 
Monoid b => Monoid (a -> b)

Since: 2.1

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

mconcat :: [a -> b] -> a -> b #

(Monoid a, Monoid b) => Monoid (a, b)

Since: 2.1

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

(Eq k, Hashable k) => Monoid (HashMap k v) 

Methods

mempty :: HashMap k v #

mappend :: HashMap k v -> HashMap k v -> HashMap k v #

mconcat :: [HashMap k v] -> HashMap k v #

Ord k => Monoid (Map k v) 

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

mconcat :: [Map k v] -> Map k v #

Monoid (Parser i a) 

Methods

mempty :: Parser i a #

mappend :: Parser i a -> Parser i a -> Parser i a #

mconcat :: [Parser i a] -> Parser i a #

Monoid (Proxy k s)

Since: 4.7.0.0

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c)

Since: 2.1

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

Monoid a => Monoid (Const k a b) 

Methods

mempty :: Const k a b #

mappend :: Const k a b -> Const k a b -> Const k a b #

mconcat :: [Const k a b] -> Const k a b #

Alternative f => Monoid (Alt * f a)

Since: 4.8.0.0

Methods

mempty :: Alt * f a #

mappend :: Alt * f a -> Alt * f a -> Alt * f a #

mconcat :: [Alt * f a] -> Alt * f a #

(Semigroup a, Monoid a) => Monoid (Tagged k s a) 

Methods

mempty :: Tagged k s a #

mappend :: Tagged k s a -> Tagged k s a -> Tagged k s a #

mconcat :: [Tagged k s a] -> Tagged k s a #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d)

Since: 2.1

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e)

Since: 2.1

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #

class ToJSON a where #

A type that can be converted to JSON.

Instances in general must specify toJSON and should (but don't need to) specify toEncoding.

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 it will probably be more efficient than the following option.
  • 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. If you require nothing other than defaultOptions, it is sufficient to write (and this is the only alternative where the default toJSON implementation is sufficient):

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

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

instance ToJSON Coord where
    toEncoding = genericToEncoding defaultOptions

If on the other hand you wish to customize the generic decoding, you have to implement both methods:

customOptions = defaultOptions
                { fieldLabelModifier = map toUpper
                }

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

Previous versions of this library only had the toJSON method. Adding toEncoding had to reasons:

  1. toEncoding is more efficient for the common case that the output of toJSON is directly serialized to a ByteString. Further, expressing either method in terms of the other would be non-optimal.
  2. The choice of defaults allows a smooth transition for existing users: Existing instances that do not define toEncoding still compile and have the correct semantics. This is ensured by making the default implementation of toEncoding use 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. (this also means that specifying nothing more than instance ToJSON Coord would be sufficient as a generically decoding instance, but there probably exists no good reason to not specify toEncoding in new instances.)

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

toJSONList :: [a] -> Value #

toEncodingList :: [a] -> Encoding #

Instances

ToJSON Bool 
ToJSON Char 
ToJSON Double 
ToJSON Float 
ToJSON Int 
ToJSON Int8 
ToJSON Int16 
ToJSON Int32 
ToJSON Int64 
ToJSON Integer 
ToJSON Natural 
ToJSON Ordering 
ToJSON Word 
ToJSON Word8 
ToJSON Word16 
ToJSON Word32 
ToJSON Word64 
ToJSON () 

Methods

toJSON :: () -> Value #

toEncoding :: () -> Encoding #

toJSONList :: [()] -> Value #

toEncodingList :: [()] -> Encoding #

ToJSON Scientific 
ToJSON Number 
ToJSON Text 
ToJSON UTCTime 
ToJSON Value 
ToJSON DotNetTime 
ToJSON Text 
ToJSON Version 
ToJSON CTime 
ToJSON IntSet 
ToJSON DiffTime 
ToJSON ZonedTime 
ToJSON LocalTime 
ToJSON TimeOfDay 
ToJSON NominalDiffTime 
ToJSON Day 
ToJSON UUID 
ToJSON PhraseSuggesterCollate # 
ToJSON PhraseSuggesterHighlighter # 
ToJSON PhraseSuggester # 
ToJSON SuggestType # 
ToJSON Suggest # 
ToJSON RestoreIndexSettings # 
ToJSON RestoreRenamePattern # 
ToJSON SnapshotName # 
ToJSON BuildHash # 
ToJSON GenericSnapshotRepoSettings # 
ToJSON SnapshotRepoType # 
ToJSON SnapshotRepoName # 
ToJSON DateMathExpr # 
ToJSON DateRangeAggRange # 
ToJSON DateRangeAggregation # 
ToJSON Aggregation # 
ToJSON Interval # 
ToJSON ExecutionHint # 
ToJSON CollectionMode # 
ToJSON TermInclusion # 
ToJSON TermOrder # 
ToJSON ScrollId # 
ToJSON TemplateQueryInline # 
ToJSON TemplateQueryKeyValuePairs # 
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 VersionNumber # 
ToJSON Version # 
ToJSON PhraseSuggesterCollate # 
ToJSON PhraseSuggesterHighlighter # 
ToJSON PhraseSuggester # 
ToJSON SuggestType # 
ToJSON Suggest # 
ToJSON RestoreIndexSettings # 
ToJSON RestoreRenamePattern # 
ToJSON SnapshotName # 
ToJSON BuildHash # 
ToJSON GenericSnapshotRepoSettings # 
ToJSON SnapshotRepoType # 
ToJSON SnapshotRepoName # 
ToJSON DateMathExpr # 
ToJSON DateRangeAggRange # 
ToJSON DateRangeAggregation # 
ToJSON Aggregation # 
ToJSON Interval # 
ToJSON ExecutionHint # 
ToJSON CollectionMode # 
ToJSON TermInclusion # 
ToJSON TermOrder # 
ToJSON ScrollId # 
ToJSON TemplateQueryInline # 
ToJSON TemplateQueryKeyValuePairs # 
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 CommonMinimumMatch # 
ToJSON CommonTermsQuery # 
ToJSON BoostingQuery # 
ToJSON BoolQuery # 
ToJSON MultiMatchQueryType # 
ToJSON MultiMatchQuery # 
ToJSON MatchQueryType # 
ToJSON MatchQuery # 
ToJSON DisMaxQuery # 
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 Filter # 
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 Tokenizer # 
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 Compression # 
ToJSON ReplicaBounds # 
ToJSON AllocationPolicy # 
ToJSON TokenChar # 
ToJSON TokenizerDefinition # 
ToJSON AnalyzerDefinition # 
ToJSON Analysis # 
ToJSON UpdatableIndexSetting # 
ToJSON IndexSettings # 
ToJSON VersionNumber # 
ToJSON Version # 
ToJSON a => ToJSON [a] 

Methods

toJSON :: [a] -> Value #

toEncoding :: [a] -> Encoding #

toJSONList :: [[a]] -> Value #

toEncodingList :: [[a]] -> Encoding #

ToJSON a => ToJSON (Maybe a) 
(ToJSON a, Integral a) => ToJSON (Ratio a) 
HasResolution a => ToJSON (Fixed a) 
ToJSON a => ToJSON (Min a) 

Methods

toJSON :: Min a -> Value #

toEncoding :: Min a -> Encoding #

toJSONList :: [Min a] -> Value #

toEncodingList :: [Min a] -> Encoding #

ToJSON a => ToJSON (Max a) 

Methods

toJSON :: Max a -> Value #

toEncoding :: Max a -> Encoding #

toJSONList :: [Max a] -> Value #

toEncodingList :: [Max a] -> Encoding #

ToJSON a => ToJSON (First a) 
ToJSON a => ToJSON (Last a) 
ToJSON a => ToJSON (WrappedMonoid a) 
ToJSON a => ToJSON (Option a) 
ToJSON a => ToJSON (NonEmpty a) 
ToJSON a => ToJSON (Identity a) 
ToJSON a => ToJSON (Dual a) 
ToJSON a => ToJSON (First a) 
ToJSON a => ToJSON (Last a) 
ToJSON a => ToJSON (IntMap a) 
ToJSON v => ToJSON (Tree v) 
ToJSON a => ToJSON (Seq a) 

Methods

toJSON :: Seq a -> Value #

toEncoding :: Seq a -> Encoding #

toJSONList :: [Seq a] -> Value #

toEncodingList :: [Seq a] -> Encoding #

ToJSON a => ToJSON (Set a) 

Methods

toJSON :: Set a -> Value #

toEncoding :: Set a -> Encoding #

toJSONList :: [Set a] -> Value #

toEncodingList :: [Set a] -> Encoding #

ToJSON a => ToJSON (DList a) 
ToJSON a => ToJSON (HashSet 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 (Vector a) 
(ToJSON a, ToJSON b) => ToJSON (Either a b) 

Methods

toJSON :: Either a b -> Value #

toEncoding :: Either a b -> Encoding #

toJSONList :: [Either a b] -> Value #

toEncodingList :: [Either a b] -> Encoding #

(ToJSON a, ToJSON b) => ToJSON (a, b) 

Methods

toJSON :: (a, b) -> Value #

toEncoding :: (a, b) -> Encoding #

toJSONList :: [(a, b)] -> Value #

toEncodingList :: [(a, b)] -> Encoding #

(ToJSON v, ToJSONKey k) => ToJSON (HashMap k v) 
(ToJSON v, ToJSONKey k) => ToJSON (Map k v) 

Methods

toJSON :: Map k v -> Value #

toEncoding :: Map k v -> Encoding #

toJSONList :: [Map k v] -> Value #

toEncodingList :: [Map k v] -> Encoding #

ToJSON (Proxy k a) 

Methods

toJSON :: Proxy k a -> Value #

toEncoding :: Proxy k a -> Encoding #

toJSONList :: [Proxy k a] -> Value #

toEncodingList :: [Proxy k a] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c) => ToJSON (a, b, c) 

Methods

toJSON :: (a, b, c) -> Value #

toEncoding :: (a, b, c) -> Encoding #

toJSONList :: [(a, b, c)] -> Value #

toEncodingList :: [(a, b, c)] -> Encoding #

ToJSON a => ToJSON (Const k a b) 

Methods

toJSON :: Const k a b -> Value #

toEncoding :: Const k a b -> Encoding #

toJSONList :: [Const k a b] -> Value #

toEncodingList :: [Const k a b] -> Encoding #

ToJSON b => ToJSON (Tagged k a b) 

Methods

toJSON :: Tagged k a b -> Value #

toEncoding :: Tagged k a b -> Encoding #

toJSONList :: [Tagged k a b] -> Value #

toEncodingList :: [Tagged k a b] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a, b, c, d) 

Methods

toJSON :: (a, b, c, d) -> Value #

toEncoding :: (a, b, c, d) -> Encoding #

toJSONList :: [(a, b, c, d)] -> Value #

toEncodingList :: [(a, b, c, d)] -> Encoding #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Product * f g a) 

Methods

toJSON :: Product * f g a -> Value #

toEncoding :: Product * f g a -> Encoding #

toJSONList :: [Product * f g a] -> Value #

toEncodingList :: [Product * f g a] -> Encoding #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Sum * f g a) 

Methods

toJSON :: Sum * f g a -> Value #

toEncoding :: Sum * f g a -> Encoding #

toJSONList :: [Sum * f g a] -> Value #

toEncodingList :: [Sum * f g a] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON (a, b, c, d, e) 

Methods

toJSON :: (a, b, c, d, e) -> Value #

toEncoding :: (a, b, c, d, e) -> Encoding #

toJSONList :: [(a, b, c, d, e)] -> Value #

toEncodingList :: [(a, b, c, d, e)] -> Encoding #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Compose * * f g a) 

Methods

toJSON :: Compose * * f g a -> Value #

toEncoding :: Compose * * f g a -> Encoding #

toJSONList :: [Compose * * f g a] -> Value #

toEncodingList :: [Compose * * f g a] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (a, b, c, d, e, f) 

Methods

toJSON :: (a, b, c, d, e, f) -> Value #

toEncoding :: (a, b, c, d, e, f) -> Encoding #

toJSONList :: [(a, b, c, d, e, f)] -> Value #

toEncodingList :: [(a, b, c, d, e, f)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON (a, b, c, d, e, f, g) 

Methods

toJSON :: (a, b, c, d, e, f, g) -> Value #

toEncoding :: (a, b, c, d, e, f, g) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g)] -> Encoding #

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

Methods

toJSON :: (a, b, c, d, e, f, g, h) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h)] -> Encoding #

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

Methods

toJSON :: (a, b, c, d, e, f, g, h, i) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i)] -> Encoding #

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

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j)] -> Encoding #

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

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Encoding #

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

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Encoding #

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

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Encoding #

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

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Encoding #

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

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Encoding #

data Interval Source #

Instances

Eq Interval Source # 
Read Interval Source # 
Show Interval Source # 
Generic Interval Source # 

Associated Types

type Rep Interval :: * -> * #

Methods

from :: Interval -> Rep Interval x #

to :: Rep Interval x -> Interval #

ToJSON Interval Source # 
type Rep Interval Source # 
type Rep Interval = D1 * (MetaData "Interval" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Year" PrefixI False) (U1 *)) (C1 * (MetaCons "Quarter" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Month" PrefixI False) (U1 *)) (C1 * (MetaCons "Week" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Day" PrefixI False) (U1 *)) (C1 * (MetaCons "Hour" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Minute" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Second" PrefixI False) (U1 *)) (C1 * (MetaCons "FractionalInterval" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Float)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TimeInterval))))))))

data TermInclusion Source #

data GenericSnapshotRepo Source #

A generic representation of a snapshot repo. This is what gets sent to and parsed from the server. For repo types enabled by plugins that aren't exported by this library, consider making a custom type which implements SnapshotRepo. If it is a common repo type, consider submitting a pull request to have it included in the library proper

data SnapshotRepoConversionError Source #

Instances

Eq SnapshotRepoConversionError Source # 
Show SnapshotRepoConversionError Source # 
Generic SnapshotRepoConversionError Source # 
Exception SnapshotRepoConversionError Source # 
type Rep SnapshotRepoConversionError Source # 
type Rep SnapshotRepoConversionError = D1 * (MetaData "SnapshotRepoConversionError" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * (C1 * (MetaCons "RepoTypeMismatch" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * SnapshotRepoType)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * SnapshotRepoType)))) (C1 * (MetaCons "OtherRepoConversionError" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))

newtype SnapshotRepoType Source #

Constructors

SnapshotRepoType 

Instances

Eq SnapshotRepoType Source # 
Ord SnapshotRepoType Source # 
Show SnapshotRepoType Source # 
Generic SnapshotRepoType Source # 
ToJSON SnapshotRepoType Source # 
FromJSON SnapshotRepoType Source # 
type Rep SnapshotRepoType Source # 
type Rep SnapshotRepoType = D1 * (MetaData "SnapshotRepoType" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "SnapshotRepoType" PrefixI True) (S1 * (MetaSel (Just Symbol "snapshotRepoType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

newtype GenericSnapshotRepoSettings Source #

Opaque representation of snapshot repo settings. Instances of SnapshotRepo will produce this.

Instances

Eq GenericSnapshotRepoSettings Source # 
Show GenericSnapshotRepoSettings Source # 
Generic GenericSnapshotRepoSettings Source # 
ToJSON GenericSnapshotRepoSettings Source # 
FromJSON GenericSnapshotRepoSettings Source # 
type Rep GenericSnapshotRepoSettings Source # 
type Rep GenericSnapshotRepoSettings = D1 * (MetaData "GenericSnapshotRepoSettings" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "GenericSnapshotRepoSettings" PrefixI True) (S1 * (MetaSel (Just Symbol "gSnapshotRepoSettingsObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Object)))

data SnapshotRepoUpdateSettings Source #

Constructors

SnapshotRepoUpdateSettings 

Fields

  • repoUpdateVerify :: Bool

    After creation/update, synchronously check that nodes can write to this repo. Defaults to True. You may use False if you need a faster response and plan on verifying manually later with verifySnapshotRepo.

defaultSnapshotRepoUpdateSettings :: SnapshotRepoUpdateSettings Source #

Reasonable defaults for repo creation/update

  • repoUpdateVerify True

newtype SnapshotRepoName Source #

The unique name of a snapshot repository.

Constructors

SnapshotRepoName 

Instances

Eq SnapshotRepoName Source # 
Ord SnapshotRepoName Source # 
Show SnapshotRepoName Source # 
Generic SnapshotRepoName Source # 
ToJSON SnapshotRepoName Source # 
FromJSON SnapshotRepoName Source # 
type Rep SnapshotRepoName Source # 
type Rep SnapshotRepoName = D1 * (MetaData "SnapshotRepoName" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "SnapshotRepoName" PrefixI True) (S1 * (MetaSel (Just Symbol "snapshotRepoName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data SnapshotRepoPattern Source #

Either specifies an exact repo name or one with globs in it, e.g. RepoPattern "foo*" NOTE: Patterns are not supported on ES < 1.7

newtype FullNodeId Source #

Unique, automatically-generated name assigned to nodes that are usually returned in node-oriented APIs.

Constructors

FullNodeId 

Fields

newtype NodeName Source #

A human-readable node name that is supplied by the user in the node config or automatically generated by ElasticSearch.

Constructors

NodeName 

Fields

Instances

Eq NodeName Source # 
Ord NodeName Source # 
Show NodeName Source # 
Generic NodeName Source # 

Associated Types

type Rep NodeName :: * -> * #

Methods

from :: NodeName -> Rep NodeName x #

to :: Rep NodeName x -> NodeName #

FromJSON NodeName Source # 
type Rep NodeName Source # 
type Rep NodeName = D1 * (MetaData "NodeName" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "NodeName" PrefixI True) (S1 * (MetaSel (Just Symbol "nodeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data NodesInfo Source #

Instances

Eq NodesInfo Source # 
Show NodesInfo Source # 
Generic NodesInfo Source # 

Associated Types

type Rep NodesInfo :: * -> * #

FromJSON NodesInfo Source # 
type Rep NodesInfo Source # 
type Rep NodesInfo = D1 * (MetaData "NodesInfo" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodesInfo" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "nodesInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [NodeInfo])) (S1 * (MetaSel (Just Symbol "nodesClusterName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ClusterName))))

data NodesStats Source #

Instances

Eq NodesStats Source # 
Show NodesStats Source # 
Generic NodesStats Source # 

Associated Types

type Rep NodesStats :: * -> * #

FromJSON NodesStats Source # 
type Rep NodesStats Source # 
type Rep NodesStats = D1 * (MetaData "NodesStats" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodesStats" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "nodesStats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [NodeStats])) (S1 * (MetaSel (Just Symbol "nodesStatsClusterName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ClusterName))))

data NodeStats Source #

Instances

Eq NodeStats Source # 
Show NodeStats Source # 
Generic NodeStats Source # 

Associated Types

type Rep NodeStats :: * -> * #

type Rep NodeStats Source # 
type Rep NodeStats = D1 * (MetaData "NodeStats" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodeStats" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeStatsName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeName)) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeStatsFullId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FullNodeId)) (S1 * (MetaSel (Just Symbol "nodeStatsBreakersStats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NodeBreakersStats))))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeStatsHTTP") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeHTTPStats)) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeStatsTransport") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeTransportStats)) (S1 * (MetaSel (Just Symbol "nodeStatsFS") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeFSStats))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeStatsNetwork") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeNetworkStats)) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeStatsThreadPool") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolsStats)) (S1 * (MetaSel (Just Symbol "nodeStatsJVM") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeJVMStats)))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeStatsProcess") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeProcessStats)) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeStatsOS") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeOSStats)) (S1 * (MetaSel (Just Symbol "nodeStatsIndices") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeIndicesStats)))))))

data NodeBreakersStats Source #

data NodeBreakerStats Source #

data NodeTransportStats Source #

Instances

Eq NodeTransportStats Source # 
Show NodeTransportStats Source # 
Generic NodeTransportStats Source # 
FromJSON NodeTransportStats Source # 
type Rep NodeTransportStats Source # 
type Rep NodeTransportStats = D1 * (MetaData "NodeTransportStats" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodeTransportStats" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeTransportTXSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "nodeTransportCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeTransportRXSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeTransportRXCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeTransportServerOpen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))))

data NodeDataPathStats Source #

Instances

Eq NodeDataPathStats Source # 
Show NodeDataPathStats Source # 
Generic NodeDataPathStats Source # 
FromJSON NodeDataPathStats Source # 
type Rep NodeDataPathStats Source # 
type Rep NodeDataPathStats = D1 * (MetaData "NodeDataPathStats" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodeDataPathStats" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeDataPathDiskServiceTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Double))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeDataPathDiskQueue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Double))) (S1 * (MetaSel (Just Symbol "nodeDataPathIOSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bytes))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeDataPathWriteSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bytes))) (S1 * (MetaSel (Just Symbol "nodeDataPathReadSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bytes)))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeDataPathIOOps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "nodeDataPathWrites") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeDataPathReads") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "nodeDataPathAvailable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeDataPathFree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "nodeDataPathTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeDataPathType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "nodeDataPathDevice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeDataPathMount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "nodeDataPathPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))))))

data NodeFSTotalStats Source #

Instances

Eq NodeFSTotalStats Source # 
Show NodeFSTotalStats Source # 
Generic NodeFSTotalStats Source # 
FromJSON NodeFSTotalStats Source # 
type Rep NodeFSTotalStats Source # 
type Rep NodeFSTotalStats = D1 * (MetaData "NodeFSTotalStats" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodeFSTotalStats" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeFSTotalDiskServiceTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Double))) (S1 * (MetaSel (Just Symbol "nodeFSTotalDiskQueue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Double)))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeFSTotalIOSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bytes))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeFSTotalWriteSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bytes))) (S1 * (MetaSel (Just Symbol "nodeFSTotalReadSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bytes)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeFSTotalIOOps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeFSTotalWrites") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "nodeFSTotalReads") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeFSTotalAvailable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeFSTotalFree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "nodeFSTotalTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)))))))

data NodeNetworkStats Source #

Instances

Eq NodeNetworkStats Source # 
Show NodeNetworkStats Source # 
Generic NodeNetworkStats Source # 
FromJSON NodeNetworkStats Source # 
type Rep NodeNetworkStats Source # 

data NodeThreadPoolsStats Source #

Instances

Eq NodeThreadPoolsStats Source # 
Show NodeThreadPoolsStats Source # 
Generic NodeThreadPoolsStats Source # 
FromJSON NodeThreadPoolsStats Source # 
type Rep NodeThreadPoolsStats Source # 
type Rep NodeThreadPoolsStats = D1 * (MetaData "NodeThreadPoolsStats" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodeThreadPoolsStats" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsSnapshot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolStats)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsBulk") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolStats))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsMerge") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolStats)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsGet") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolStats)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsManagement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolStats)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsFetchShardStore") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NodeThreadPoolStats)))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsOptimize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolStats)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsFlush") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolStats))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsSearch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolStats)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsWarmer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolStats))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsGeneric") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolStats)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsSuggest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolStats)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsRefresh") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolStats)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolStats))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsListener") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NodeThreadPoolStats))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsFetchShardStarted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NodeThreadPoolStats))) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsStatsPercolate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolStats))))))))

data NodeThreadPoolStats Source #

Instances

Eq NodeThreadPoolStats Source # 
Show NodeThreadPoolStats Source # 
Generic NodeThreadPoolStats Source # 
FromJSON NodeThreadPoolStats Source # 
type Rep NodeThreadPoolStats Source # 
type Rep NodeThreadPoolStats = D1 * (MetaData "NodeThreadPoolStats" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodeThreadPoolStats" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolCompleted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolLargest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolRejected") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolActive") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolQueue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolThreads") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))))

data NodeJVMStats Source #

Instances

Eq NodeJVMStats Source # 
Show NodeJVMStats Source # 
Generic NodeJVMStats Source # 

Associated Types

type Rep NodeJVMStats :: * -> * #

FromJSON NodeJVMStats Source # 
type Rep NodeJVMStats Source # 
type Rep NodeJVMStats = D1 * (MetaData "NodeJVMStats" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodeJVMStats" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeJVMStatsMappedBufferPool") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * JVMBufferPoolStats)) (S1 * (MetaSel (Just Symbol "nodeJVMStatsDirectBufferPool") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * JVMBufferPoolStats))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeJVMStatsGCOldCollector") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * JVMGCStats)) (S1 * (MetaSel (Just Symbol "nodeJVMStatsGCYoungCollector") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * JVMGCStats)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeJVMStatsPeakThreadsCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeJVMStatsThreadsCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeJVMStatsOldPool") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * JVMPoolStats)) (S1 * (MetaSel (Just Symbol "nodeJVMStatsSurvivorPool") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * JVMPoolStats))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeJVMStatsYoungPool") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * JVMPoolStats)) (S1 * (MetaSel (Just Symbol "nodeJVMStatsNonHeapCommitted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeJVMStatsNonHeapUsed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "nodeJVMStatsHeapMax") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeJVMStatsHeapCommitted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "nodeJVMStatsHeapUsedPercent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeJVMStatsHeapUsed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeJVMStatsUptime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime)) (S1 * (MetaSel (Just Symbol "nodeJVMStatsTimestamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * UTCTime))))))))

data JVMBufferPoolStats Source #

data JVMGCStats Source #

Instances

Eq JVMGCStats Source # 
Show JVMGCStats Source # 
Generic JVMGCStats Source # 

Associated Types

type Rep JVMGCStats :: * -> * #

FromJSON JVMGCStats Source # 
type Rep JVMGCStats Source # 
type Rep JVMGCStats = D1 * (MetaData "JVMGCStats" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "JVMGCStats" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "jvmGCStatsCollectionTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime)) (S1 * (MetaSel (Just Symbol "jvmGCStatsCollectionCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))

data NodeProcessStats Source #

Instances

Eq NodeProcessStats Source # 
Show NodeProcessStats Source # 
Generic NodeProcessStats Source # 
FromJSON NodeProcessStats Source # 
type Rep NodeProcessStats Source # 

data NodeOSStats Source #

Instances

Eq NodeOSStats Source # 
Show NodeOSStats Source # 
Generic NodeOSStats Source # 

Associated Types

type Rep NodeOSStats :: * -> * #

FromJSON NodeOSStats Source # 
type Rep NodeOSStats Source # 
type Rep NodeOSStats = D1 * (MetaData "NodeOSStats" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodeOSStats" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeOSSwapFree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "nodeOSSwapUsed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeOSMemActualUsed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "nodeOSMemActualFree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeOSMemUsedPercent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeOSMemFreePercent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeOSMemUsed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "nodeOSMemFree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeOSCPUStolen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeOSCPUUsage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeOSCPUIdle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeOSCPUUser") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeOSCPUSys") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeOSLoad") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LoadAvgs)))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeOSUptime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime)) (S1 * (MetaSel (Just Symbol "nodeOSTimestamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * UTCTime)))))))

data LoadAvgs Source #

Instances

Eq LoadAvgs Source # 
Show LoadAvgs Source # 
Generic LoadAvgs Source # 

Associated Types

type Rep LoadAvgs :: * -> * #

Methods

from :: LoadAvgs -> Rep LoadAvgs x #

to :: Rep LoadAvgs x -> LoadAvgs #

FromJSON LoadAvgs Source # 
type Rep LoadAvgs Source # 
type Rep LoadAvgs = D1 * (MetaData "LoadAvgs" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "LoadAvgs" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "loadAvg1Min") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)) ((:*:) * (S1 * (MetaSel (Just Symbol "loadAvg5Min") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)) (S1 * (MetaSel (Just Symbol "loadAvg15Min") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)))))

data NodeIndicesStats Source #

Constructors

NodeIndicesStats 

Fields

Instances

Eq NodeIndicesStats Source # 
Show NodeIndicesStats Source # 
Generic NodeIndicesStats Source # 
FromJSON NodeIndicesStats Source # 
type Rep NodeIndicesStats Source # 
type Rep NodeIndicesStats = D1 * (MetaData "NodeIndicesStats" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodeIndicesStats" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsRecoveryThrottleTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NominalDiffTime))) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsRecoveryCurrentAsTarget") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsRecoveryCurrentAsSource") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsQueryCacheMisses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsQueryCacheHits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsQueryCacheEvictions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsQueryCacheSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bytes))) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSuggestCurrent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSuggestTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSuggestTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsTranslogSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsTranslogOps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSegFixedBitSetMemory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bytes))) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSegVersionMapMemory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSegIndexWriterMaxMemory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bytes))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSegIndexWriterMemory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSegMemory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes))))))) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSegCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsCompletionSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsPercolateQueries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsPercolateMemory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsPercolateCurrent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsPercolateTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsPercolateTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsFieldDataEvictions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsFieldDataMemory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsIDCacheMemory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsFilterCacheEvictions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsFilterCacheMemory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsWarmerTotalTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsWarmerTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsWarmerCurrent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsFlushTotalTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime)) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsFlushTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsRefreshTotalTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime)))))))) ((:*:) * ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsRefreshTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsMergesTotalSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsMergesTotalDocs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsMergesTotalTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsMergesTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsMergesCurrentSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsMergesCurrentDocs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsMergesCurrent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSearchFetchCurrent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSearchFetchTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSearchFetchTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSearchQueryCurrent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSearchQueryTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSearchQueryTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsSearchOpenContexts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsGetCurrent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsGetMissingTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime))))))) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsGetMissingTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsGetExistsTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsGetExistsTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsGetTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsGetTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsIndexingThrottleTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NominalDiffTime)))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsIndexingIsThrottled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsIndexingNoopUpdateTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsIndexingDeleteCurrent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsIndexingDeleteTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsIndexingDeleteTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsIndexingIndexCurrent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsIndexingIndexTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsIndexingTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsStoreThrottleTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NominalDiffTime))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsStoreSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bytes)) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeIndicesStatsDocsDeleted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "nodeIndicesStatsDocsCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))))))))

newtype EsAddress Source #

A quirky address format used throughout ElasticSearch. An example would be inet[/1.1.1.1:9200]. inet may be a placeholder for a FQDN.

Constructors

EsAddress 

Fields

data NodeInfo Source #

Instances

Eq NodeInfo Source # 
Show NodeInfo Source # 
Generic NodeInfo Source # 

Associated Types

type Rep NodeInfo :: * -> * #

Methods

from :: NodeInfo -> Rep NodeInfo x #

to :: Rep NodeInfo x -> NodeInfo #

type Rep NodeInfo Source # 
type Rep NodeInfo = D1 * (MetaData "NodeInfo" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodeInfo" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeInfoHTTPAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EsAddress)) (S1 * (MetaSel (Just Symbol "nodeInfoBuild") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * BuildHash))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeInfoESVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * VersionNumber)) (S1 * (MetaSel (Just Symbol "nodeInfoIP") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Server)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeInfoHost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Server)) (S1 * (MetaSel (Just Symbol "nodeInfoTransportAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EsAddress))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeInfoName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeName)) (S1 * (MetaSel (Just Symbol "nodeInfoFullId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FullNodeId))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeInfoPlugins") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [NodePluginInfo])) (S1 * (MetaSel (Just Symbol "nodeInfoHTTP") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeHTTPInfo))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeInfoTransport") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeTransportInfo)) (S1 * (MetaSel (Just Symbol "nodeInfoNetwork") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeNetworkInfo)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeInfoThreadPool") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolsInfo)) (S1 * (MetaSel (Just Symbol "nodeInfoJVM") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeJVMInfo))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeInfoProcess") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeProcessInfo)) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeInfoOS") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeOSInfo)) (S1 * (MetaSel (Just Symbol "nodeInfoSettings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Object))))))))

data NodePluginInfo Source #

Constructors

NodePluginInfo 

Fields

newtype NetworkInterfaceName Source #

Instances

Eq NetworkInterfaceName Source # 
Ord NetworkInterfaceName Source # 
Show NetworkInterfaceName Source # 
Generic NetworkInterfaceName Source # 
FromJSON NetworkInterfaceName Source # 
type Rep NetworkInterfaceName Source # 
type Rep NetworkInterfaceName = D1 * (MetaData "NetworkInterfaceName" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "NetworkInterfaceName" PrefixI True) (S1 * (MetaSel (Just Symbol "networkInterfaceName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data NodeNetworkInterface Source #

data NodeThreadPoolsInfo Source #

Instances

Eq NodeThreadPoolsInfo Source # 
Show NodeThreadPoolsInfo Source # 
Generic NodeThreadPoolsInfo Source # 
FromJSON NodeThreadPoolsInfo Source # 
type Rep NodeThreadPoolsInfo Source # 
type Rep NodeThreadPoolsInfo = D1 * (MetaData "NodeThreadPoolsInfo" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodeThreadPoolsInfo" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsRefresh") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolInfo)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsManagement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolInfo))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsPercolate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolInfo)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsListener") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NodeThreadPoolInfo))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsFetchShardStarted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NodeThreadPoolInfo))) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsSearch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolInfo))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsFlush") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolInfo)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsWarmer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolInfo))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsOptimize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolInfo)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsBulk") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolInfo))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsSuggest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolInfo)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsMerge") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolInfo)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsSnapshot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolInfo)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsGet") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolInfo))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsFetchShardStore") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NodeThreadPoolInfo))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolsIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolInfo)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolsGeneric") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NodeThreadPoolInfo))))))))

data NodeThreadPoolInfo Source #

Instances

Eq NodeThreadPoolInfo Source # 
Show NodeThreadPoolInfo Source # 
Generic NodeThreadPoolInfo Source # 
FromJSON NodeThreadPoolInfo Source # 
type Rep NodeThreadPoolInfo Source # 
type Rep NodeThreadPoolInfo = D1 * (MetaData "NodeThreadPoolInfo" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "NodeThreadPoolInfo" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolQueueSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ThreadPoolSize)) (S1 * (MetaSel (Just Symbol "nodeThreadPoolKeepalive") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NominalDiffTime)))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolMin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "nodeThreadPoolMax") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "nodeThreadPoolType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ThreadPoolType))))))

data ThreadPoolType Source #

Instances

Eq ThreadPoolType Source # 
Show ThreadPoolType Source # 
Generic ThreadPoolType Source # 

Associated Types

type Rep ThreadPoolType :: * -> * #

FromJSON ThreadPoolType Source # 
type Rep ThreadPoolType Source # 
type Rep ThreadPoolType = D1 * (MetaData "ThreadPoolType" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * (C1 * (MetaCons "ThreadPoolScaling" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ThreadPoolFixed" PrefixI False) (U1 *)) (C1 * (MetaCons "ThreadPoolCached" PrefixI False) (U1 *))))

data NodeJVMInfo Source #

Instances

Eq NodeJVMInfo Source # 
Show NodeJVMInfo Source # 
Generic NodeJVMInfo Source # 

Associated Types

type Rep NodeJVMInfo :: * -> * #

FromJSON NodeJVMInfo Source # 
type Rep NodeJVMInfo Source # 

newtype JVMMemoryPool Source #

Constructors

JVMMemoryPool 

Fields

data JVMMemoryInfo Source #

newtype PID Source #

Constructors

PID 

Fields

Instances

Eq PID Source # 

Methods

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

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

Show PID Source # 

Methods

showsPrec :: Int -> PID -> ShowS #

show :: PID -> String #

showList :: [PID] -> ShowS #

Generic PID Source # 

Associated Types

type Rep PID :: * -> * #

Methods

from :: PID -> Rep PID x #

to :: Rep PID x -> PID #

FromJSON PID Source # 
type Rep PID Source # 
type Rep PID = D1 * (MetaData "PID" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "PID" PrefixI True) (S1 * (MetaSel (Just Symbol "pid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))

data NodeOSInfo Source #

data CPUInfo Source #

Instances

Eq CPUInfo Source # 

Methods

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

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

Show CPUInfo Source # 
Generic CPUInfo Source # 

Associated Types

type Rep CPUInfo :: * -> * #

Methods

from :: CPUInfo -> Rep CPUInfo x #

to :: Rep CPUInfo x -> CPUInfo #

FromJSON CPUInfo Source # 
type Rep CPUInfo Source # 

data NodeProcessInfo Source #

data FsSnapshotRepo Source #

A filesystem-based snapshot repo that ships with ElasticSearch. This is an instance of SnapshotRepo so it can be used with updateSnapshotRepo

Constructors

FsSnapshotRepo 

Fields

Instances

Eq FsSnapshotRepo Source # 
Show FsSnapshotRepo Source # 
Generic FsSnapshotRepo Source # 

Associated Types

type Rep FsSnapshotRepo :: * -> * #

SnapshotRepo FsSnapshotRepo Source # 
type Rep FsSnapshotRepo Source # 
type Rep FsSnapshotRepo = D1 * (MetaData "FsSnapshotRepo" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "FsSnapshotRepo" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fsrName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * SnapshotRepoName)) ((:*:) * (S1 * (MetaSel (Just Symbol "fsrLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath)) (S1 * (MetaSel (Just Symbol "fsrCompressMetadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "fsrChunkSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bytes))) ((:*:) * (S1 * (MetaSel (Just Symbol "fsrMaxRestoreBytesPerSec") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bytes))) (S1 * (MetaSel (Just Symbol "fsrMaxSnapshotBytesPerSec") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bytes)))))))

data SnapshotCreateSettings Source #

Constructors

SnapshotCreateSettings 

Fields

  • snapWaitForCompletion :: Bool

    Should the API call return immediately after initializing the snapshot or wait until completed? Note that if this is enabled it could wait a long time, so you should adjust your ManagerSettings accordingly to set long timeouts or explicitly handle timeouts.

  • snapIndices :: Maybe IndexSelection

    Nothing will snapshot all indices. Just [] is permissable and will essentially be a no-op snapshot.

  • snapIgnoreUnavailable :: Bool

    If set to True, any matched indices that don't exist will be ignored. Otherwise it will be an error and fail.

  • snapIncludeGlobalState :: Bool
     
  • snapPartial :: Bool

    If some indices failed to snapshot (e.g. if not all primary shards are available), should the process proceed?

Instances

defaultSnapshotCreateSettings :: SnapshotCreateSettings Source #

Reasonable defaults for snapshot creation

  • snapWaitForCompletion False
  • snapIndices Nothing
  • snapIgnoreUnavailable False
  • snapIncludeGlobalState True
  • snapPartial False

data SnapshotPattern Source #

Either specifies an exact snapshot name or one with globs in it, e.g. SnapPattern "foo*" NOTE: Patterns are not supported on ES < 1.7

data SnapshotInfo Source #

General information about the state of a snapshot. Has some redundancies with SnapshotStatus

Instances

Eq SnapshotInfo Source # 
Show SnapshotInfo Source # 
Generic SnapshotInfo Source # 

Associated Types

type Rep SnapshotInfo :: * -> * #

FromJSON SnapshotInfo Source # 
type Rep SnapshotInfo Source # 

data SnapshotShardFailure Source #

Instances

Eq SnapshotShardFailure Source # 
Show SnapshotShardFailure Source # 
Generic SnapshotShardFailure Source # 
FromJSON SnapshotShardFailure Source # 
type Rep SnapshotShardFailure Source # 
type Rep SnapshotShardFailure = D1 * (MetaData "SnapshotShardFailure" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "SnapshotShardFailure" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "snapShardFailureIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * IndexName)) (S1 * (MetaSel (Just Symbol "snapShardFailureNodeId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe NodeName)))) ((:*:) * (S1 * (MetaSel (Just Symbol "snapShardFailureReason") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "snapShardFailureShardId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ShardId)))))

newtype ShardId Source #

Constructors

ShardId 

Fields

Instances

Eq ShardId Source # 

Methods

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

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

Show ShardId Source # 
Generic ShardId Source # 

Associated Types

type Rep ShardId :: * -> * #

Methods

from :: ShardId -> Rep ShardId x #

to :: Rep ShardId x -> ShardId #

FromJSON ShardId Source # 
type Rep ShardId Source # 
type Rep ShardId = D1 * (MetaData "ShardId" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "ShardId" PrefixI True) (S1 * (MetaSel (Just Symbol "shardId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))

newtype SnapshotName Source #

Constructors

SnapshotName 

Fields

data SnapshotState Source #

Instances

Eq SnapshotState Source # 
Show SnapshotState Source # 
Generic SnapshotState Source # 

Associated Types

type Rep SnapshotState :: * -> * #

FromJSON SnapshotState Source # 
type Rep SnapshotState Source # 
type Rep SnapshotState = D1 * (MetaData "SnapshotState" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "SnapshotInit" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SnapshotStarted" PrefixI False) (U1 *)) (C1 * (MetaCons "SnapshotSuccess" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "SnapshotFailed" PrefixI False) (U1 *)) (C1 * (MetaCons "SnapshotAborted" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "SnapshotMissing" PrefixI False) (U1 *)) (C1 * (MetaCons "SnapshotWaiting" PrefixI False) (U1 *)))))

data SnapshotRestoreSettings Source #

Constructors

SnapshotRestoreSettings 

Fields

Instances

Eq SnapshotRestoreSettings Source # 
Show SnapshotRestoreSettings Source # 
Generic SnapshotRestoreSettings Source # 
type Rep SnapshotRestoreSettings Source # 
type Rep SnapshotRestoreSettings = D1 * (MetaData "SnapshotRestoreSettings" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "SnapshotRestoreSettings" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "snapRestoreWaitForCompletion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "snapRestoreIndices") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe IndexSelection)))) ((:*:) * (S1 * (MetaSel (Just Symbol "snapRestoreIgnoreUnavailable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "snapRestoreIncludeGlobalState") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "snapRestoreRenamePattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe RestoreRenamePattern)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "snapRestoreRenameReplacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (NonEmpty RestoreRenameToken)))) (S1 * (MetaSel (Just Symbol "snapRestorePartial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "snapRestoreIncludeAliases") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "snapRestoreIndexSettingsOverrides") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe RestoreIndexSettings))) (S1 * (MetaSel (Just Symbol "snapRestoreIgnoreIndexSettings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (NonEmpty Text)))))))))

defaultSnapshotRestoreSettings :: SnapshotRestoreSettings Source #

Reasonable defaults for snapshot restores

  • snapRestoreWaitForCompletion False
  • snapRestoreIndices Nothing
  • snapRestoreIgnoreUnavailable False
  • snapRestoreIncludeGlobalState True
  • snapRestoreRenamePattern Nothing
  • snapRestoreRenameReplacement Nothing
  • snapRestorePartial False
  • snapRestoreIncludeAliases True
  • snapRestoreIndexSettingsOverrides Nothing
  • snapRestoreIgnoreIndexSettings Nothing

newtype RestoreRenamePattern Source #

Regex-stype pattern, e.g. "index_(.+)" to match index names

Constructors

RestoreRenamePattern 

Fields

Instances

Eq RestoreRenamePattern Source # 
Ord RestoreRenamePattern Source # 
Show RestoreRenamePattern Source # 
Generic RestoreRenamePattern Source # 
ToJSON RestoreRenamePattern Source # 
type Rep RestoreRenamePattern Source # 
type Rep RestoreRenamePattern = D1 * (MetaData "RestoreRenamePattern" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" True) (C1 * (MetaCons "RestoreRenamePattern" PrefixI True) (S1 * (MetaSel (Just Symbol "rrPattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data RestoreRenameToken Source #

A single token in a index renaming scheme for a restore. These are concatenated into a string before being sent to ElasticSearch. Check out these Java docs to find out more if you're into that sort of thing.

Constructors

RRTLit Text

Just a literal string of characters

RRSubWholeMatch

Equivalent to $0. The entire matched pattern, not any subgroup

RRSubGroup RRGroupRefNum

A specific reference to a group number

mkRRGroupRefNum :: Int -> Maybe RRGroupRefNum Source #

Only allows valid group number references (1-9).

data RestoreIndexSettings Source #

Index settings that can be overridden. The docs only mention you can update number of replicas, but there may be more. You definitely cannot override shard count.

data Suggest Source #

data PhraseSuggester Source #

Instances

Eq PhraseSuggester Source # 
Read PhraseSuggester Source # 
Show PhraseSuggester Source # 
Generic PhraseSuggester Source # 
ToJSON PhraseSuggester Source # 
FromJSON PhraseSuggester Source # 
type Rep PhraseSuggester Source # 
type Rep PhraseSuggester = D1 * (MetaData "PhraseSuggester" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "PhraseSuggester" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "phraseSuggesterField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FieldName)) (S1 * (MetaSel (Just Symbol "phraseSuggesterGramSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "phraseSuggesterRealWordErrorLikelihood") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "phraseSuggesterConfidence") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "phraseSuggesterMaxErrors") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "phraseSuggesterSeparator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "phraseSuggesterSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Size))) (S1 * (MetaSel (Just Symbol "phraseSuggesterAnalyzer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Analyzer))))) ((:*:) * (S1 * (MetaSel (Just Symbol "phraseSuggesterShardSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "phraseSuggesterHighlight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PhraseSuggesterHighlighter))) (S1 * (MetaSel (Just Symbol "phraseSuggesterCollate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PhraseSuggesterCollate))))))))

data PhraseSuggesterHighlighter Source #

Instances

Eq PhraseSuggesterHighlighter Source # 
Read PhraseSuggesterHighlighter Source # 
Show PhraseSuggesterHighlighter Source # 
Generic PhraseSuggesterHighlighter Source # 
ToJSON PhraseSuggesterHighlighter Source # 
FromJSON PhraseSuggesterHighlighter Source # 
type Rep PhraseSuggesterHighlighter Source # 
type Rep PhraseSuggesterHighlighter = D1 * (MetaData "PhraseSuggesterHighlighter" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "PhraseSuggesterHighlighter" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "phraseSuggesterHighlighterPreTag") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "phraseSuggesterHighlighterPostTag") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))

data PhraseSuggesterCollate Source #

Instances

Eq PhraseSuggesterCollate Source # 
Read PhraseSuggesterCollate Source # 
Show PhraseSuggesterCollate Source # 
Generic PhraseSuggesterCollate Source # 
ToJSON PhraseSuggesterCollate Source # 
FromJSON PhraseSuggesterCollate Source # 
type Rep PhraseSuggesterCollate Source # 
type Rep PhraseSuggesterCollate = D1 * (MetaData "PhraseSuggesterCollate" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "PhraseSuggesterCollate" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "phraseSuggesterCollateTemplateQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TemplateQueryInline)) (S1 * (MetaSel (Just Symbol "phraseSuggesterCollatePrune") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))))

data Aggregation Source #

Instances

Eq Aggregation Source # 
Read Aggregation Source # 
Show Aggregation Source # 
Generic Aggregation Source # 

Associated Types

type Rep Aggregation :: * -> * #

ToJSON Aggregation Source # 
type Rep Aggregation Source # 

data Bucket a Source #

Constructors

Bucket 

Fields

data TermsAggregation Source #

Instances

Eq TermsAggregation Source # 
Read TermsAggregation Source # 
Show TermsAggregation Source # 
Generic TermsAggregation Source # 
type Rep TermsAggregation Source # 
type Rep TermsAggregation = D1 * (MetaData "TermsAggregation" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "TermsAggregation" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "term") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Either Text Text))) (S1 * (MetaSel (Just Symbol "termInclude") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TermInclusion)))) ((:*:) * (S1 * (MetaSel (Just Symbol "termExclude") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TermInclusion))) ((:*:) * (S1 * (MetaSel (Just Symbol "termOrder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TermOrder))) (S1 * (MetaSel (Just Symbol "termMinDocCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "termSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "termShardSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "termCollectMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe CollectionMode))) ((:*:) * (S1 * (MetaSel (Just Symbol "termExecutionHint") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe ExecutionHint))) (S1 * (MetaSel (Just Symbol "termAggs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Aggregations))))))))

data ValueCountAggregation Source #

data FilterAggregation Source #

data DateHistogramAggregation Source #

Instances

Eq DateHistogramAggregation Source # 
Read DateHistogramAggregation Source # 
Show DateHistogramAggregation Source # 
Generic DateHistogramAggregation Source # 
type Rep DateHistogramAggregation Source # 

data DateRangeAggregation Source #

Instances

Eq DateRangeAggregation Source # 
Read DateRangeAggregation Source # 
Show DateRangeAggregation Source # 
Generic DateRangeAggregation Source # 
ToJSON DateRangeAggregation Source # 
type Rep DateRangeAggregation Source # 
type Rep DateRangeAggregation = D1 * (MetaData "DateRangeAggregation" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) (C1 * (MetaCons "DateRangeAggregation" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "draField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FieldName)) ((:*:) * (S1 * (MetaSel (Just Symbol "draFormat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "draRanges") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (NonEmpty DateRangeAggRange))))))

data DateRangeAggRange Source #

Instances

Eq DateRangeAggRange Source # 
Read DateRangeAggRange Source # 
Show DateRangeAggRange Source # 
Generic DateRangeAggRange Source # 
ToJSON DateRangeAggRange Source # 
type Rep DateRangeAggRange Source # 

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 

data DateMathModifier Source #

Instances

Eq DateMathModifier Source # 
Read DateMathModifier Source # 
Show DateMathModifier Source # 
Generic DateMathModifier Source # 
type Rep DateMathModifier Source # 

data DateMathUnit Source #

Instances

Eq DateMathUnit Source # 
Read DateMathUnit Source # 
Show DateMathUnit Source # 
Generic DateMathUnit Source # 

Associated Types

type Rep DateMathUnit :: * -> * #

type Rep DateMathUnit Source # 
type Rep DateMathUnit = D1 * (MetaData "DateMathUnit" "Database.V1.Bloodhound.Types" "bloodhound-0.15.0.1-8AOKIjoqRdsAKgOHF7WzLM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "DMYear" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "DMMonth" PrefixI False) (U1 *)) (C1 * (MetaCons "DMWeek" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "DMDay" PrefixI False) (U1 *)) (C1 * (MetaCons "DMHour" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "DMMinute" PrefixI False) (U1 *)) (C1 * (MetaCons "DMSecond" PrefixI False) (U1 *)))))

data HighlightSettings Source #

Instances

Eq HighlightSettings Source # 
Read HighlightSettings Source # 
Show HighlightSettings Source # 
Generic HighlightSettings Source # 
ToJSON HighlightSettings Source # 
type Rep HighlightSettings Source # 

data FastVectorHighlight Source #

Instances

Eq FastVectorHighlight Source # 
Read FastVectorHighlight Source # 
Show FastVectorHighlight Source # 
Generic FastVectorHighlight Source # 
type Rep FastVectorHighlight Source # 

data CommonHighlight Source #

Instances

Eq CommonHighlight Source # 
Read CommonHighlight Source # 
Show CommonHighlight Source # 
Generic CommonHighlight Source # 
type Rep CommonHighlight Source # 

data DateRangeResult Source #

Instances

Eq DateRangeResult Source # 
Read DateRangeResult Source # 
Show DateRangeResult Source # 
Generic DateRangeResult Source # 
FromJSON DateRangeResult Source # 
BucketAggregation DateRangeResult Source # 
type Rep DateRangeResult Source # 

newtype EsUsername Source #

Username type used for HTTP Basic authentication. See basicAuthHook.

Constructors

EsUsername 

Fields

newtype EsPassword Source #

Password type used for HTTP Basic authentication. See basicAuthHook.

Constructors

EsPassword 

Fields