bloodhound-0.18.0.0: Elasticsearch client library for Haskell
Copyright(C) 2014 2018 Chris Allen
LicenseBSD-style (see the file LICENSE)
MaintainerChris Allen <cma@bitemyapp.com
Stabilityprovisional
PortabilityRecordWildCards
Safe HaskellNone
LanguageHaskell2010

Database.Bloodhound.Types

Description

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

Synopsis

Documentation

defaultIndexDocumentSettings :: IndexDocumentSettings Source #

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

mkSort :: FieldName -> SortOrder -> DefaultSort Source #

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

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

unpackId :: DocId -> Text Source #

unpackId is a silly convenience function that gets used once.

mkMatchQuery :: FieldName -> QueryString -> MatchQuery Source #

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

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

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

mkDocVersion :: Int -> Maybe DocVersion Source #

Smart constructor for in-range doc version

newtype BH m a Source #

Constructors

BH 

Fields

Instances

Instances details
MonadTrans BH Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

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

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

Defined in Database.Bloodhound.Internal.Client

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 # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

get :: BH m s #

put :: s -> BH m () #

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

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

Defined in Database.Bloodhound.Internal.Client

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 # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

throwError :: e -> BH m a #

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

Monad m => Monad (BH m) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

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 #

Functor m => Functor (BH m) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

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

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

MonadFix m => MonadFix (BH m) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

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

MonadFail m => MonadFail (BH m) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

fail :: String -> BH m a #

Applicative m => Applicative (BH m) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

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 # 
Instance details

Defined in Database.Bloodhound.Internal.Client

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 # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

mzero :: BH m a #

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

MonadIO m => MonadIO (BH m) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

liftIO :: IO a -> BH m a #

MonadThrow m => MonadThrow (BH m) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

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

MonadCatch m => MonadCatch (BH m) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

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

MonadMask m => MonadMask (BH m) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

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 #

generalBracket :: BH m a -> (a -> ExitCase b -> BH m c) -> (a -> BH m b) -> BH m (b, c) #

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

Defined in Database.Bloodhound.Internal.Client

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.

Instances

Instances details
(Functor m, Applicative m, MonadIO m) => MonadBH (ReaderT BHEnv m) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

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

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

mkBHEnv :: Server -> Manager -> BHEnv Source #

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

> (mkBHEnv myServer myManager) { bhRequestHook = customHook }

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

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

Methods

getBHEnv :: m BHEnv Source #

Instances

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

Defined in Database.Bloodhound.Internal.Client

Methods

getBHEnv :: BH m BHEnv Source #

(Functor m, Applicative m, MonadIO m) => MonadBH (ReaderT BHEnv m) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

newtype MaybeNA a Source #

Constructors

MaybeNA 

Fields

Instances

Instances details
Eq a => Eq (MaybeNA a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

Methods

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

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

Show a => Show (MaybeNA a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

Methods

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

show :: MaybeNA a -> String #

showList :: [MaybeNA a] -> ShowS #

FromJSON a => FromJSON (MaybeNA a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

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 

Instances

Instances details
Eq Status Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

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

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

Show Status Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

FromJSON Status Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

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 
CompressionSetting Compression 
IndexCompoundFormat CompoundFormat 
IndexCompoundOnFlush Bool 
WarmerEnabled Bool 
MappingTotalFieldsLimit Int 
AnalysisSetting Analysis

Analysis is not a dynamic setting and can only be performed on a closed index.

UnassignedNodeLeftDelayedTimeout NominalDiffTime

Sets a delay to the allocation of replica shards which become unassigned because a node has left, giving them chance to return. See https://www.elastic.co/guide/en/elasticsearch/reference/5.6/delayed-allocation.html

data AllocationPolicy Source #

Constructors

AllocAll

Allows shard allocation for all shards.

AllocPrimaries

Allows shard allocation only for primary shards.

AllocNewPrimaries

Allows shard allocation only for primary shards for new indices.

AllocNone

No shard allocation is allowed

data Compression Source #

Constructors

CompressionDefault

Compress with LZ4

CompressionBest

Compress with DEFLATE. Elastic blogs that this can reduce disk use by 15%-25%.

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

Instances details
Eq Bytes Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

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

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

Ord Bytes Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

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 #

Show Bytes Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

ToJSON Bytes Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

FromJSON Bytes Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

data FSType Source #

Constructors

FSSimple 
FSBuffered 

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

Instances details
Eq Server Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

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

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

Show Server Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

FromJSON Server Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

type Reply = Response LByteString 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

Instances details
Eq a => Eq (EsResult a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

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

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

Show a => Show (EsResult a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

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

show :: EsResult a -> String #

showList :: [EsResult a] -> ShowS #

FromJSON a => FromJSON (EsResult a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

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

Instances details
Eq a => Eq (EsResultFound a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Show a => Show (EsResultFound a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

FromJSON a => FromJSON (EsResultFound a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

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

Instances details
Eq EsError Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

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

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

Show EsError Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

FromJSON EsError Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

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.

Constructors

EsProtocolException 

Fields

data DocVersion Source #

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

Instances

Instances details
Bounded DocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Enum DocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Eq DocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Ord DocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Show DocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON DocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

FromJSON DocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

newtype ExternalDocVersion Source #

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

Instances

Instances details
Bounded ExternalDocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Enum ExternalDocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Eq ExternalDocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Ord ExternalDocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Show ExternalDocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON ExternalDocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

data VersionControl Source #

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

Constructors

NoVersionControl

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

InternalVersion DocVersion

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

ExternalGT ExternalDocVersion

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

ExternalGTE ExternalDocVersion

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

ForceVersion ExternalDocVersion

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

data IndexDocumentSettings Source #

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

data Query Source #

Instances

Instances details
Eq Query Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

Methods

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

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

Show Query Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

ToJSON Query Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

FromJSON Query Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

data Search Source #

Instances

Instances details
Eq Search Source # 
Instance details

Defined in Database.Bloodhound.Types

Methods

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

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

Show Search Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON Search Source # 
Instance details

Defined in Database.Bloodhound.Types

data SearchResult a Source #

Constructors

SearchResult 

Fields

Instances

Instances details
Eq a => Eq (SearchResult a) Source # 
Instance details

Defined in Database.Bloodhound.Types

Show a => Show (SearchResult a) Source # 
Instance details

Defined in Database.Bloodhound.Types

FromJSON a => FromJSON (SearchResult a) Source # 
Instance details

Defined in Database.Bloodhound.Types

data SearchHits a Source #

Constructors

SearchHits 

Fields

newtype From Source #

Constructors

From Int 

Instances

Instances details
Eq From Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

Methods

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

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

Show From Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

Methods

showsPrec :: Int -> From -> ShowS #

show :: From -> String #

showList :: [From] -> ShowS #

ToJSON From Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

newtype Size Source #

Constructors

Size Int 

Instances

Instances details
Eq Size Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

Methods

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

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

Show Size Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

ToJSON Size Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

FromJSON Size Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

data Source Source #

Instances

Instances details
Eq Source Source # 
Instance details

Defined in Database.Bloodhound.Types

Methods

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

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

Show Source Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON Source Source # 
Instance details

Defined in Database.Bloodhound.Types

data Include Source #

Constructors

Include [Pattern] 

Instances

Instances details
Eq Include Source # 
Instance details

Defined in Database.Bloodhound.Types

Methods

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

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

Read Include Source # 
Instance details

Defined in Database.Bloodhound.Types

Show Include Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON Include Source # 
Instance details

Defined in Database.Bloodhound.Types

data Exclude Source #

Constructors

Exclude [Pattern] 

Instances

Instances details
Eq Exclude Source # 
Instance details

Defined in Database.Bloodhound.Types

Methods

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

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

Read Exclude Source # 
Instance details

Defined in Database.Bloodhound.Types

Show Exclude Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON Exclude Source # 
Instance details

Defined in Database.Bloodhound.Types

newtype Pattern Source #

Constructors

Pattern Text 

Instances

Instances details
Eq Pattern Source # 
Instance details

Defined in Database.Bloodhound.Types

Methods

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

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

Read Pattern Source # 
Instance details

Defined in Database.Bloodhound.Types

Show Pattern Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON Pattern Source # 
Instance details

Defined in Database.Bloodhound.Types

data Hit a Source #

Instances

Instances details
Eq a => Eq (Hit a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

Methods

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

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

Show a => Show (Hit a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

Methods

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

show :: Hit a -> String #

showList :: [Hit a] -> ShowS #

FromJSON a => FromJSON (Hit a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

Methods

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

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

newtype Filter Source #

As of Elastic 2.0, Filters are just Queries housed in a Bool Query, and flagged in a different context.

Constructors

Filter 

Fields

Instances

Instances details
Eq Filter Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

Methods

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

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

Show Filter Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON Filter Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

FromJSON Filter Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

data Term Source #

Constructors

Term 

Fields

Instances

Instances details
Eq Term Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

Methods

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

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

Show Term Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

Methods

showsPrec :: Int -> Term -> ShowS #

show :: Term -> String #

showList :: [Term] -> ShowS #

ToJSON Term Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

FromJSON Term Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

data GeoPoint Source #

Constructors

GeoPoint 

data LatLon Source #

Constructors

LatLon 

Fields

Instances

Instances details
Eq LatLon Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

Methods

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

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

Show LatLon Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON LatLon Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

FromJSON LatLon Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

newtype LessThan Source #

Constructors

LessThan Double 

Instances

Instances details
Eq LessThan Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

Show LessThan Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

newtype LessThanEq Source #

Constructors

LessThanEq Double 

Instances

Instances details
Eq LessThanEq Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

Show LessThanEq Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

newtype GreaterThan Source #

Constructors

GreaterThan Double 

Instances

Instances details
Eq GreaterThan Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

Show GreaterThan Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

newtype LessThanD Source #

Constructors

LessThanD UTCTime 

Instances

Instances details
Eq LessThanD Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

Show LessThanD Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

newtype LessThanEqD Source #

Constructors

LessThanEqD UTCTime 

Instances

Instances details
Eq LessThanEqD Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

Show LessThanEqD Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

newtype Regexp Source #

Constructors

Regexp Text 

Instances

Instances details
Eq Regexp Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

Methods

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

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

Show Regexp Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

FromJSON Regexp Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

newtype FieldName Source #

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

Constructors

FieldName Text 

newtype IndexName Source #

IndexName is used to describe which index to querycreatedelete

Constructors

IndexName Text 

data IndexSelection Source #

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

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 

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

Constructors

ForceMergeIndexSettings 

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.

defaultForceMergeIndexSettings :: ForceMergeIndexSettings Source #

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

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

Instances details
Eq DocId Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

Methods

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

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

Show DocId Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

Methods

showsPrec :: Int -> DocId -> ShowS #

show :: DocId -> String #

showList :: [DocId] -> ShowS #

ToJSON DocId Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

FromJSON DocId Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

newtype CacheName Source #

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

Constructors

CacheName Text 

newtype CacheKey Source #

CacheKey is used in RegexpFilter to key regex caching.

Constructors

CacheKey Text 

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. Consult the Bulk API documentation for further explanation. Warning: Bulk operations suffixed with Auto rely on Elasticsearch to generate the id. Often, people use auto-generated identifiers when Elasticsearch is the only place that their data is stored. Do not let Elasticsearch be the only place your data is stored. It does not guarantee durability, and it may silently discard data. This issue is discussed further on github.

Constructors

BulkIndex IndexName DocId Value

Create the document, replacing it if it already exists.

BulkIndexAuto IndexName Value

Create a document with an autogenerated id.

BulkIndexEncodingAuto IndexName Encoding

Create a document with an autogenerated id. Use fast JSON encoding.

BulkCreate IndexName DocId Value

Create a document, failing if it already exists.

BulkCreateEncoding IndexName DocId Encoding

Create a document, failing if it already exists. Use fast JSON encoding.

BulkDelete IndexName DocId

Delete the document

BulkUpdate IndexName DocId Value

Update the document, merging the new value with the existing one.

BulkUpsert IndexName DocId UpsertPayload [UpsertActionMetadata]

Update the document if it already exists, otherwise insert it.

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

The ignoreUnmapped, when Just field is used to set the elastic unmapped_type

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

Instances

Instances details
Eq DefaultSort Source # 
Instance details

Defined in Database.Bloodhound.Internal.Sort

Show DefaultSort Source # 
Instance details

Defined in Database.Bloodhound.Internal.Sort

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

Instances details
Eq Missing Source # 
Instance details

Defined in Database.Bloodhound.Internal.Sort

Methods

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

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

Show Missing Source # 
Instance details

Defined in Database.Bloodhound.Internal.Sort

ToJSON Missing Source # 
Instance details

Defined in Database.Bloodhound.Internal.Sort

newtype Boost Source #

Constructors

Boost Double 

Instances

Instances details
Eq Boost Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

Methods

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

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

Show Boost Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

Methods

showsPrec :: Int -> Boost -> ShowS #

show :: Boost -> String #

showList :: [Boost] -> ShowS #

ToJSON Boost Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

FromJSON Boost Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

newtype Weight Source #

Constructors

Weight Float 

Instances

Instances details
Eq Weight Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

Methods

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

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

Show Weight Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

ToJSON Weight Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

FromJSON Weight Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

newtype Seed Source #

Constructors

Seed Float 

Instances

Instances details
Eq Seed Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

Methods

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

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

Show Seed Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

Methods

showsPrec :: Int -> Seed -> ShowS #

show :: Seed -> String #

showList :: [Seed] -> ShowS #

ToJSON Seed Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

FromJSON Seed Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

newtype Factor Source #

Constructors

Factor Float 

Instances

Instances details
Eq Factor Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

Methods

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

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

Show Factor Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

ToJSON Factor Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

FromJSON Factor Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

data MoreLikeThisQuery Source #

data MoreLikeThisFieldQuery Source #

data QueryStringQuery Source #

newtype Lenient Source #

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

Constructors

Lenient Bool 

newtype MinimumMatch Source #

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

Constructors

MinimumMatch Int 

newtype IgnoreUnmapped Source #

Indicates whether to ignore an unmapped parent_type and not return any documents instead of an error.

Constructors

IgnoreUnmapped Bool 

newtype MinChildren Source #

Maximum number of child documents that match the query allowed for a returned parent document. If the parent document exceeds this limit, it is excluded from the search results.

Constructors

MinChildren Int 

newtype MaxChildren Source #

Minimum number of child documents that match the query required to match the query for a returned parent document. If the parent document does not meet this limit, it is excluded from the search results.

Constructors

MaxChildren Int 

type Cache = Bool Source #

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

newtype PhraseSlop Source #

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

Constructors

PhraseSlop Int 

newtype 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

Instances details
Eq Mapping Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

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

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

Show Mapping Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

newtype AllowLeadingWildcard Source #

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

newtype Locale Source #

Locale is used for string conversions - defaults to ROOT.

Constructors

Locale Text 

class Semigroup a => Monoid a where #

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

Right identity
x <> mempty = x
Left identity
mempty <> x = x
Associativity
x <> (y <> z) = (x <> y) <> z (Semigroup law)
Concatenation
mconcat = foldr (<>) 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.

NOTE: Semigroup is a superclass of Monoid since base-4.11.0.0.

Minimal complete definition

mempty

Methods

mempty :: a #

Identity of mappend

>>> "Hello world" <> mempty
"Hello world"

mappend :: a -> a -> a #

An associative operation

NOTE: This method is redundant and has the default implementation mappend = (<>) since base-4.11.0.0. Should it be implemented manually, since mappend is a synonym for (<>), it is expected that the two functions are defined the same way. In a future GHC release mappend will be removed from Monoid.

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.

>>> mconcat ["Hello", " ", "Haskell", "!"]
"Hello Haskell!"

Instances

Instances details
Monoid Ordering

Since: base-2.1

Instance details

Defined in GHC.Base

Monoid ()

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: () #

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

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

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Monoid Builder 
Instance details

Defined in Data.ByteString.Builder.Internal

Monoid Series 
Instance details

Defined in Data.Aeson.Encoding.Internal

Monoid More 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

mempty :: More #

mappend :: More -> More -> More #

mconcat :: [More] -> More #

Monoid All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

Monoid IntSet 
Instance details

Defined in Data.IntSet.Internal

Monoid CookieJar

Since 1.9

Instance details

Defined in Network.HTTP.Client.Types

Monoid RequestBody 
Instance details

Defined in Network.HTTP.Client.Types

Monoid ByteArray 
Instance details

Defined in Data.Primitive.ByteArray

Monoid CalendarDiffTime

Additive

Instance details

Defined in Data.Time.LocalTime.Internal.CalendarDiffTime

Monoid CalendarDiffDays

Additive

Instance details

Defined in Data.Time.Calendar.CalendarDiffDays

Monoid [a]

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: [a] #

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

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

Semigroup 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 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: Maybe a #

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

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

Monoid a => Monoid (IO a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

mempty :: IO a #

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

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

Monoid p => Monoid (Par1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Par1 p #

mappend :: Par1 p -> Par1 p -> Par1 p #

mconcat :: [Par1 p] -> Par1 p #

Monoid (IResult a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

mempty :: IResult a #

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

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

Monoid (Result a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

mempty :: Result a #

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

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

Monoid (Parser a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

mempty :: Parser a #

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

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

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

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Min a #

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

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

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

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Max a #

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

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

Monoid m => Monoid (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Semigroup a => Monoid (Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Option a #

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

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

Monoid a => Monoid (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mempty :: Identity a #

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

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

Monoid (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: First a #

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

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

Monoid (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: Last a #

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

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

Monoid a => Monoid (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Dual a #

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

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

Monoid (Endo a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Endo a #

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

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

Num a => Monoid (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Sum a #

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

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

Num a => Monoid (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Product a #

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

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

Monoid a => Monoid (Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

mempty :: Down a #

mappend :: Down a -> Down a -> Down a #

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

Monoid s => Monoid (CI s) 
Instance details

Defined in Data.CaseInsensitive.Internal

Methods

mempty :: CI s #

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

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

Monoid (IntMap a) 
Instance details

Defined in Data.IntMap.Internal

Methods

mempty :: IntMap a #

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

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

Monoid (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

mempty :: Seq a #

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

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

Ord a => Monoid (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

mempty :: Set a #

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

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

Monoid (DList a) 
Instance details

Defined in Data.DList.Internal

Methods

mempty :: DList a #

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

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

Monoid (PrimArray a)

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.PrimArray

Monoid (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Monoid (Array a) 
Instance details

Defined in Data.Primitive.Array

Methods

mempty :: Array a #

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

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

Semigroup a => Monoid (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

mempty :: Maybe a #

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

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

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

mempty = empty

mappend = union

O(n+m)

To obtain good performance, the smaller set must be presented as the first argument.

Examples

Expand
>>> mappend (fromList [1,2]) (fromList [2,3])
fromList [1,2,3]
Instance details

Defined in Data.HashSet.Internal

Methods

mempty :: HashSet a #

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

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

Storable a => Monoid (Vector a) 
Instance details

Defined in Data.Vector.Storable

Methods

mempty :: Vector a #

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

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

Prim a => Monoid (Vector a) 
Instance details

Defined in Data.Vector.Primitive

Methods

mempty :: Vector a #

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

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

Monoid (Vector a) 
Instance details

Defined in Data.Vector

Methods

mempty :: Vector a #

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

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

Monoid (MergeSet a) 
Instance details

Defined in Data.Set.Internal

Methods

mempty :: MergeSet a #

mappend :: MergeSet a -> MergeSet a -> MergeSet a #

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

Monoid (SearchHits a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

Monoid b => Monoid (a -> b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: a -> b #

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

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

Monoid (U1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: U1 p #

mappend :: U1 p -> U1 p -> U1 p #

mconcat :: [U1 p] -> U1 p #

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

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b) #

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

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

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

mempty = empty

mappend = union

If a key occurs in both maps, the mapping from the first will be the mapping in the result.

Examples

Expand
>>> mappend (fromList [(1,'a'),(2,'b')]) (fromList [(2,'c'),(3,'d')])
fromList [(1,'a'),(2,'b'),(3,'d')]
Instance details

Defined in Data.HashMap.Internal

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) 
Instance details

Defined in Data.Map.Internal

Methods

mempty :: Map k v #

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

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

Monoid a => Monoid (ST s a)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

mempty :: ST s a #

mappend :: ST s a -> ST s a -> ST s a #

mconcat :: [ST s a] -> ST s a #

Monoid (Parser i a) 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

mempty :: Parser i a #

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

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

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

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

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

(Monoid a, Monoid b) => Monoid (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

mempty :: Pair a b #

mappend :: Pair a b -> Pair a b -> Pair a b #

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

Monoid (f p) => Monoid (Rec1 f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Rec1 f p #

mappend :: Rec1 f p -> Rec1 f p -> Rec1 f p #

mconcat :: [Rec1 f p] -> Rec1 f p #

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

Since: base-2.1

Instance details

Defined in GHC.Base

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 a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

mempty :: Const a b #

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

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

(Applicative f, Monoid a) => Monoid (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mempty :: Ap f a #

mappend :: Ap f a -> Ap f a -> Ap f a #

mconcat :: [Ap f a] -> Ap f a #

Alternative f => Monoid (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

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 s a) 
Instance details

Defined in Data.Tagged

Methods

mempty :: Tagged s a #

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

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

Monoid c => Monoid (K1 i c p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: K1 i c p #

mappend :: K1 i c p -> K1 i c p -> K1 i c p #

mconcat :: [K1 i c p] -> K1 i c p #

(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :*: g) p #

mappend :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

mconcat :: [(f :*: g) p] -> (f :*: g) p #

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

Since: base-2.1

Instance details

Defined in GHC.Base

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 (f p) => Monoid (M1 i c f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: M1 i c f p #

mappend :: M1 i c f p -> M1 i c f p -> M1 i c f p #

mconcat :: [M1 i c f p] -> M1 i c f p #

Monoid (f (g p)) => Monoid ((f :.: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :.: g) p #

mappend :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p #

mconcat :: [(f :.: g) p] -> (f :.: g) p #

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

Since: base-2.1

Instance details

Defined in GHC.Base

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 two 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.)

Minimal complete definition

Nothing

Methods

toJSON :: a -> Value #

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

toEncoding :: a -> Encoding #

Encode a Haskell value as JSON.

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

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

instance ToJSON Coord where
    toEncoding = genericToEncoding defaultOptions

toJSONList :: [a] -> Value #

toEncodingList :: [a] -> Encoding #

Instances

Instances details
ToJSON Bool 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Char 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Double 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Float 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int8 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int16 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int32 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int64 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Ordering 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word8 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word16 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word32 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word64 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON () 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: () -> Value #

toEncoding :: () -> Encoding #

toJSONList :: [()] -> Value #

toEncodingList :: [()] -> Encoding #

ToJSON Scientific 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Value 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON DotNetTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Number 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Void 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Version 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON CTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON IntSet 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON ZonedTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON LocalTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON TimeOfDay 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON CalendarDiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON SystemTime

Encoded as number

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON NominalDiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON DiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON DayOfWeek 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Day 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON CalendarDiffDays 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON QuarterOfYear 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Quarter 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Month 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON UUID 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON CharFilter Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON TokenFilter Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON SnapshotName Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON IndexAliasName Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON IndexName Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON ShardCount Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON ReplicaCount Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON BoostTerms Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON Boost Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON MaxChildren Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON MinChildren Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON IgnoreUnmapped Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON AggregateParentScore Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON MaxDocFrequency Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON MinDocFrequency Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON PhraseSlop Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON MinWordLength Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON MaxWordLength Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON Locale Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON GeneratePhraseQueries Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON AnalyzeWildcard Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON EnablePositionIncrements Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON LowercaseExpanded Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON AllowLeadingWildcard Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON QueryPath Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON StopWord Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON PercentMatch Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON PrefixLength Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON MaxQueryTerms Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON MinimumTermFrequency Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON IgnoreTermFrequency Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON DisableCoord Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON MinimumMatch Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON Tiebreaker Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON Lenient Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON MaxExpansions Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON Analyzer Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON CutoffFrequency Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON NullValue Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON Existence Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON CacheKey Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON CacheName Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON QueryString Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON RelationName Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON FieldName Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON DocId Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON Size Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON From Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

ToJSON FactorMissingFieldValue Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

ToJSON FactorModifier Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

ToJSON Factor Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

ToJSON FieldValueFactor Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

ToJSON Seed Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

ToJSON Weight Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

ToJSON ScoreMode Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

ToJSON BoostMode Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

ToJSON ScriptParams Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

ToJSON ScriptLanguage Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

ToJSON Script Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

ToJSON ScriptFields Source # 
Instance details

Defined in Database.Bloodhound.Common.Script

ToJSON Fuzziness Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON ComponentFunctionScoreFunction Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON FunctionScoreQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON BooleanOperator Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON TemplateQueryKeyValuePairs Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON Distance Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON OptimizeBbox Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON DistanceType Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON DistanceUnit Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON GeoPoint Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON GeoBoundingBoxConstraint Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON GeoBoundingBox Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON LatLon Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON GeoFilterType Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON BoolMatch Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON Term Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON RegexpFlags Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON RangeExecution Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON ZeroTermsQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON CommonMinimumMatch Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON CommonTermsQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON BoostingQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON BoolQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON MultiMatchQueryType Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON MultiMatchQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON MatchQueryType Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON MatchQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON DisMaxQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON FuzzyLikeThisQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON FuzzyLikeFieldQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON FuzzyQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON ScoreType Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON HasChildQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON HasParentQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON IndicesQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON MoreLikeThisQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON MoreLikeThisFieldQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON NestedQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON PrefixQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON FieldOrFields Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON QueryStringQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON SimpleQueryFlag Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON SimpleQueryStringQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON RangeQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON WildcardQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON RegexpQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON Filter Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON Query Source # 
Instance details

Defined in Database.Bloodhound.Internal.Query

ToJSON HighlightEncoder Source # 
Instance details

Defined in Database.Bloodhound.Internal.Highlight

ToJSON HighlightSettings Source # 
Instance details

Defined in Database.Bloodhound.Internal.Highlight

ToJSON FieldHighlight Source # 
Instance details

Defined in Database.Bloodhound.Internal.Highlight

ToJSON Highlights Source # 
Instance details

Defined in Database.Bloodhound.Internal.Highlight

ToJSON CountQuery Source # 
Instance details

Defined in Database.Bloodhound.Internal.Count

ToJSON Missing Source # 
Instance details

Defined in Database.Bloodhound.Internal.Sort

ToJSON SortOrder Source # 
Instance details

Defined in Database.Bloodhound.Internal.Sort

ToJSON SortSpec Source # 
Instance details

Defined in Database.Bloodhound.Internal.Sort

ToJSON SortMode Source # 
Instance details

Defined in Database.Bloodhound.Internal.Sort

ToJSON Language Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

ToJSON TokenFilterDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

ToJSON TokenChar Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

ToJSON TokenizerDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

ToJSON CharFilterDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

ToJSON AnalyzerDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

ToJSON Tokenizer Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

ToJSON Analysis Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

ToJSON Interval Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON RestoreIndexSettings Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON RestoreRenamePattern Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON VMVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON BuildHash Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON GenericSnapshotRepoSettings Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON SnapshotRepoType Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON SnapshotRepoName Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON IndexPattern Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON TemplateName Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON ExternalDocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON DocVersion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON RoutingValue Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON IndexAliasRouting Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON SearchAliasRouting Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON AliasRouting Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON IndexAliasCreate Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON IndexAliasAction Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON IndexAlias Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON AllocationPolicy Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON IndexTemplate Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON NominalDiffTimeJSON Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON CompoundFormat Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON InitialShardCount Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON FSType Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON Bytes Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON Compression Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON ReplicaBounds Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON UpdatableIndexSetting Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON IndexSettings Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON VersionNumber Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON Version Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

ToJSON DateMathExpr Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

ToJSON ExecutionHint Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

ToJSON CollectionMode Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

ToJSON TermOrder Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

ToJSON TermInclusion Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

ToJSON DateRangeAggRange Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

ToJSON DateRangeAggregation Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

ToJSON Aggregation Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

ToJSON DirectGenerators Source # 
Instance details

Defined in Database.Bloodhound.Internal.Suggest

ToJSON DirectGeneratorSuggestModeTypes Source # 
Instance details

Defined in Database.Bloodhound.Internal.Suggest

ToJSON PhraseSuggesterCollate Source # 
Instance details

Defined in Database.Bloodhound.Internal.Suggest

ToJSON PhraseSuggesterHighlighter Source # 
Instance details

Defined in Database.Bloodhound.Internal.Suggest

ToJSON PhraseSuggester Source # 
Instance details

Defined in Database.Bloodhound.Internal.Suggest

ToJSON SuggestType Source # 
Instance details

Defined in Database.Bloodhound.Internal.Suggest

ToJSON Suggest Source # 
Instance details

Defined in Database.Bloodhound.Internal.Suggest

ToJSON SearchTemplate Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON SearchTemplateSource Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON SearchTemplateId Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON ScrollId Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON Pattern Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON Exclude Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON Include Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON PatternOrPatterns Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON Source Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON SearchType Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON Search Source # 
Instance details

Defined in Database.Bloodhound.Types

ToJSON a => ToJSON [a] 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: [a] -> Value #

toEncoding :: [a] -> Encoding #

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

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

ToJSON a => ToJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(ToJSON a, Integral a) => ToJSON (Ratio a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Min a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Min a -> Value #

toEncoding :: Min a -> Encoding #

toJSONList :: [Min a] -> Value #

toEncodingList :: [Min a] -> Encoding #

ToJSON a => ToJSON (Max a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Max a -> Value #

toEncoding :: Max a -> Encoding #

toJSONList :: [Max a] -> Value #

toEncodingList :: [Max a] -> Encoding #

ToJSON a => ToJSON (First a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (WrappedMonoid a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Option a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Identity a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (First a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Dual a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (NonEmpty a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (IntMap a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON v => ToJSON (Tree v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Seq a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Seq a -> Value #

toEncoding :: Seq a -> Encoding #

toJSONList :: [Seq a] -> Value #

toEncodingList :: [Seq a] -> Encoding #

ToJSON a => ToJSON (Set a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Set a -> Value #

toEncoding :: Set a -> Encoding #

toJSONList :: [Set a] -> Value #

toEncodingList :: [Set a] -> Encoding #

ToJSON1 f => ToJSON (Fix f)

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Fix f -> Value #

toEncoding :: Fix f -> Encoding #

toJSONList :: [Fix f] -> Value #

toEncodingList :: [Fix f] -> Encoding #

(ToJSON1 f, Functor f) => ToJSON (Mu f)

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Mu f -> Value #

toEncoding :: Mu f -> Encoding #

toJSONList :: [Mu f] -> Value #

toEncodingList :: [Mu f] -> Encoding #

(ToJSON1 f, Functor f) => ToJSON (Nu f)

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Nu f -> Value #

toEncoding :: Nu f -> Encoding #

toJSONList :: [Nu f] -> Value #

toEncodingList :: [Nu f] -> Encoding #

ToJSON a => ToJSON (DNonEmpty a)

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (DList a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Prim a, ToJSON a) => ToJSON (PrimArray a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (SmallArray a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Array a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Maybe a)

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (HashSet a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Storable a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Prim a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(ToJSON a, ToJSON b) => ToJSON (Either a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(ToJSON v, ToJSONKey k) => ToJSON (Map k v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Map k v -> Value #

toEncoding :: Map k v -> Encoding #

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

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

HasResolution a => ToJSON (Fixed a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Pair a b -> Value #

toEncoding :: Pair a b -> Encoding #

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

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

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

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: These a b -> Value #

toEncoding :: These a b -> Encoding #

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

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

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

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

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 (These a b)

Since: aeson-1.5.1.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: These a b -> Value #

toEncoding :: These a b -> Encoding #

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

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

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

Defined in Data.Aeson.Types.ToJSON

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 a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Const a b -> Value #

toEncoding :: Const a b -> Encoding #

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

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

ToJSON b => ToJSON (Tagged a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Tagged a b -> Value #

toEncoding :: Tagged a b -> Encoding #

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

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

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (These1 f g a)

Since: aeson-1.5.1.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: These1 f g a -> Value #

toEncoding :: These1 f g a -> Encoding #

toJSONList :: [These1 f g a] -> Value #

toEncodingList :: [These1 f g a] -> Encoding #

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

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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

newtype SnapshotRepoType Source #

Constructors

SnapshotRepoType 

newtype 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 

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

data NodeIndicesStats Source #

Constructors

NodeIndicesStats 

Fields

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

newtype PID Source #

Constructors

PID 

Fields

Instances

Instances details
Eq PID Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

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

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

Show PID Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

Methods

showsPrec :: Int -> PID -> ShowS #

show :: PID -> String #

showList :: [PID] -> ShowS #

FromJSON PID Source # 
Instance details

Defined in Database.Bloodhound.Internal.Client

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

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?

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

newtype ShardId Source #

Constructors

ShardId 

Fields

Instances

Instances details
Eq ShardId Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

Methods

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

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

Show ShardId Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

FromJSON ShardId Source # 
Instance details

Defined in Database.Bloodhound.Internal.Newtypes

data SnapshotRestoreSettings Source #

Constructors

SnapshotRestoreSettings 

Fields

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

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

newtype 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 PhraseSuggester Source #

data Bucket a Source #

Constructors

Bucket 

Fields

Instances

Instances details
Read a => Read (Bucket a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

Show a => Show (Bucket a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

Methods

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

show :: Bucket a -> String #

showList :: [Bucket a] -> ShowS #

FromJSON a => FromJSON (Bucket a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

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 TopHitResult a Source #

Constructors

TopHitResult 

Fields

Instances

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

Defined in Database.Bloodhound.Internal.Aggregation

FromJSON a => FromJSON (TopHitResult a) Source # 
Instance details

Defined in Database.Bloodhound.Internal.Aggregation

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

data Ngram Source #

Constructors

Ngram 

Instances

Instances details
Eq Ngram Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Methods

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

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

Show Ngram Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Methods

showsPrec :: Int -> Ngram -> ShowS #

show :: Ngram -> String #

showList :: [Ngram] -> ShowS #

data Language Source #

The set of languages that can be passed to various analyzers, filters, etc. in Elasticsearch. Most data types in this module that have a Language field are actually only actually to handle a subset of these languages. Consult the official Elasticsearch documentation to see what is actually supported.