Copyright | (C) 2014 Chris Allen |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Chris Allen <cma@bitemyapp.com |
Stability | provisional |
Portability | DeriveGeneric, RecordWildCards |
Safe Haskell | None |
Language | Haskell2010 |
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 Query
s and Filter
s. Filter
s are more like
traditional database constraints and often have preferable performance
properties. Query
s support human-written textual queries, such as fuzzy
queries.
- defaultCache :: Cache
- defaultIndexSettings :: IndexSettings
- defaultIndexDocumentSettings :: IndexDocumentSettings
- mkSort :: FieldName -> SortOrder -> DefaultSort
- showText :: Show a => a -> Text
- unpackId :: DocId -> Text
- mkMatchQuery :: FieldName -> QueryString -> MatchQuery
- mkMultiMatchQuery :: [FieldName] -> QueryString -> MultiMatchQuery
- mkBoolQuery :: [Query] -> [Query] -> [Query] -> BoolQuery
- mkRangeQuery :: FieldName -> RangeValue -> RangeQuery
- mkQueryStringQuery :: QueryString -> QueryStringQuery
- mkAggregations :: Text -> Aggregation -> Aggregations
- mkTermsAggregation :: Text -> TermsAggregation
- mkTermsScriptAggregation :: Text -> TermsAggregation
- mkDateHistogram :: FieldName -> Interval -> DateHistogramAggregation
- mkDocVersion :: Int -> Maybe DocVersion
- docVersionNumber :: DocVersion -> Int
- toTerms :: Text -> AggregationResults -> Maybe (Bucket TermsResult)
- toDateHistogram :: Text -> AggregationResults -> Maybe (Bucket DateHistogramResult)
- omitNulls :: [(Text, Value)] -> Value
- data BH m a
- runBH :: BHEnv -> BH m a -> m a
- data BHEnv = BHEnv {}
- class (Functor m, Applicative m, MonadIO m) => MonadBH m where
- data Version = Version {
- number :: Text
- build_hash :: Text
- build_timestamp :: UTCTime
- build_snapshot :: Bool
- lucene_version :: Text
- data Status = Status {}
- newtype Existence = Existence Bool
- newtype NullValue = NullValue Bool
- data IndexSettings = IndexSettings {}
- newtype Server = Server Text
- type Reply = Response ByteString
- data EsResult a = EsResult {}
- data DocVersion
- newtype ExternalDocVersion = ExternalDocVersion DocVersion
- data VersionControl
- data IndexDocumentSettings = IndexDocumentSettings {}
- data Query
- = TermQuery Term (Maybe Boost)
- | TermsQuery (NonEmpty Term)
- | QueryMatchQuery MatchQuery
- | QueryMultiMatchQuery MultiMatchQuery
- | QueryBoolQuery BoolQuery
- | QueryBoostingQuery BoostingQuery
- | QueryCommonTermsQuery CommonTermsQuery
- | ConstantScoreFilter Filter Boost
- | ConstantScoreQuery Query Boost
- | QueryDisMaxQuery DisMaxQuery
- | QueryFilteredQuery FilteredQuery
- | QueryFuzzyLikeThisQuery FuzzyLikeThisQuery
- | QueryFuzzyLikeFieldQuery FuzzyLikeFieldQuery
- | QueryFuzzyQuery FuzzyQuery
- | QueryHasChildQuery HasChildQuery
- | QueryHasParentQuery HasParentQuery
- | IdsQuery MappingName [DocId]
- | QueryIndicesQuery IndicesQuery
- | MatchAllQuery (Maybe Boost)
- | QueryMoreLikeThisQuery MoreLikeThisQuery
- | QueryMoreLikeThisFieldQuery MoreLikeThisFieldQuery
- | QueryNestedQuery NestedQuery
- | QueryPrefixQuery PrefixQuery
- | QueryQueryStringQuery QueryStringQuery
- | QuerySimpleQueryStringQuery SimpleQueryStringQuery
- | QueryRangeQuery RangeQuery
- | QueryRegexpQuery RegexpQuery
- data Search = Search {}
- data SearchResult a = SearchResult {
- took :: Int
- timedOut :: Bool
- shards :: ShardResult
- searchHits :: SearchHits a
- aggregations :: Maybe AggregationResults
- data SearchHits a = SearchHits {}
- type TrackSortScores = Bool
- newtype From = From Int
- newtype Size = Size Int
- data ShardResult = ShardResult {
- shardTotal :: Int
- shardsSuccessful :: Int
- shardsFailed :: Int
- data Hit a = Hit {
- hitIndex :: IndexName
- hitType :: MappingName
- hitDocId :: DocId
- hitScore :: Score
- hitSource :: a
- hitHighlight :: Maybe HitHighlight
- data Filter
- = AndFilter [Filter] Cache
- | OrFilter [Filter] Cache
- | NotFilter Filter Cache
- | IdentityFilter
- | BoolFilter BoolMatch
- | ExistsFilter FieldName
- | GeoBoundingBoxFilter GeoBoundingBoxConstraint
- | GeoDistanceFilter GeoPoint Distance DistanceType OptimizeBbox Cache
- | GeoDistanceRangeFilter GeoPoint DistanceRange
- | GeoPolygonFilter FieldName [LatLon]
- | IdsFilter MappingName [DocId]
- | LimitFilter Int
- | MissingFilter FieldName Existence NullValue
- | PrefixFilter FieldName PrefixValue Cache
- | QueryFilter Query Cache
- | RangeFilter FieldName RangeValue RangeExecution Cache
- | RegexpFilter FieldName Regexp RegexpFlags CacheName Cache CacheKey
- | TermFilter Term Cache
- class Monoid a => Seminearring a where
- data BoolMatch
- data Term = Term {}
- data GeoPoint = GeoPoint {}
- data GeoBoundingBoxConstraint = GeoBoundingBoxConstraint {}
- data GeoBoundingBox = GeoBoundingBox {
- topLeft :: LatLon
- bottomRight :: LatLon
- data GeoFilterType
- data Distance = Distance {}
- data DistanceUnit
- = Miles
- | Yards
- | Feet
- | Inches
- | Kilometers
- | Meters
- | Centimeters
- | Millimeters
- | NauticalMiles
- data DistanceType
- data DistanceRange = DistanceRange {}
- data OptimizeBbox
- data LatLon = LatLon {}
- data RangeValue
- = RangeDateLte LessThanEqD
- | RangeDateLt LessThanD
- | RangeDateGte GreaterThanEqD
- | RangeDateGt GreaterThanD
- | RangeDateGtLt GreaterThanD LessThanD
- | RangeDateGteLte GreaterThanEqD LessThanEqD
- | RangeDateGteLt GreaterThanEqD LessThanD
- | RangeDateGtLte GreaterThanD LessThanEqD
- | RangeDoubleLte LessThanEq
- | RangeDoubleLt LessThan
- | RangeDoubleGte GreaterThanEq
- | RangeDoubleGt GreaterThan
- | RangeDoubleGtLt GreaterThan LessThan
- | RangeDoubleGteLte GreaterThanEq LessThanEq
- | RangeDoubleGteLt GreaterThanEq LessThan
- | RangeDoubleGtLte GreaterThan LessThanEq
- data RangeExecution
- newtype LessThan = LessThan Double
- newtype LessThanEq = LessThanEq Double
- newtype GreaterThan = GreaterThan Double
- newtype GreaterThanEq = GreaterThanEq Double
- newtype LessThanD = LessThanD UTCTime
- newtype LessThanEqD = LessThanEqD UTCTime
- newtype GreaterThanD = GreaterThanD UTCTime
- newtype GreaterThanEqD = GreaterThanEqD UTCTime
- newtype Regexp = Regexp Text
- data RegexpFlags
- = AllRegexpFlags
- | NoRegexpFlags
- | SomeRegexpFlags (NonEmpty RegexpFlag)
- data RegexpFlag
- newtype FieldName = FieldName Text
- newtype IndexName = IndexName Text
- newtype MappingName = MappingName Text
- newtype DocId = DocId Text
- newtype CacheName = CacheName Text
- newtype CacheKey = CacheKey Text
- data BulkOperation
- = BulkIndex IndexName MappingName DocId Value
- | BulkCreate IndexName MappingName DocId Value
- | BulkDelete IndexName MappingName DocId
- | BulkUpdate IndexName MappingName DocId Value
- newtype ReplicaCount = ReplicaCount Int
- newtype ShardCount = ShardCount Int
- type Sort = [SortSpec]
- data SortMode
- data SortOrder
- data SortSpec
- data DefaultSort = DefaultSort {}
- data Missing
- = LastMissing
- | FirstMissing
- | CustomMissing Text
- data OpenCloseIndex
- type Method = Method
- newtype Boost = Boost Double
- data MatchQuery = MatchQuery {
- matchQueryField :: FieldName
- matchQueryQueryString :: QueryString
- matchQueryOperator :: BooleanOperator
- matchQueryZeroTerms :: ZeroTermsQuery
- matchQueryCutoffFrequency :: Maybe CutoffFrequency
- matchQueryMatchType :: Maybe MatchQueryType
- matchQueryAnalyzer :: Maybe Analyzer
- matchQueryMaxExpansions :: Maybe MaxExpansions
- matchQueryLenient :: Maybe Lenient
- data MultiMatchQuery = MultiMatchQuery {
- multiMatchQueryFields :: [FieldName]
- multiMatchQueryString :: QueryString
- multiMatchQueryOperator :: BooleanOperator
- multiMatchQueryZeroTerms :: ZeroTermsQuery
- multiMatchQueryTiebreaker :: Maybe Tiebreaker
- multiMatchQueryType :: Maybe MultiMatchQueryType
- multiMatchQueryCutoffFrequency :: Maybe CutoffFrequency
- multiMatchQueryAnalyzer :: Maybe Analyzer
- multiMatchQueryMaxExpansions :: Maybe MaxExpansions
- multiMatchQueryLenient :: Maybe Lenient
- data BoolQuery = BoolQuery {}
- data BoostingQuery = BoostingQuery {}
- data CommonTermsQuery = CommonTermsQuery {
- commonField :: FieldName
- commonQuery :: QueryString
- commonCutoffFrequency :: CutoffFrequency
- commonLowFreqOperator :: BooleanOperator
- commonHighFreqOperator :: BooleanOperator
- commonMinimumShouldMatch :: Maybe CommonMinimumMatch
- commonBoost :: Maybe Boost
- commonAnalyzer :: Maybe Analyzer
- commonDisableCoord :: Maybe DisableCoord
- data DisMaxQuery = DisMaxQuery {}
- data FilteredQuery = FilteredQuery {}
- data FuzzyLikeThisQuery = FuzzyLikeThisQuery {}
- data FuzzyLikeFieldQuery = FuzzyLikeFieldQuery {}
- data FuzzyQuery = FuzzyQuery {}
- data HasChildQuery = HasChildQuery {}
- data HasParentQuery = HasParentQuery {}
- data IndicesQuery = IndicesQuery {}
- data MoreLikeThisQuery = MoreLikeThisQuery {
- moreLikeThisText :: Text
- moreLikeThisFields :: Maybe [FieldName]
- moreLikeThisPercentMatch :: Maybe PercentMatch
- moreLikeThisMinimumTermFreq :: Maybe MinimumTermFrequency
- moreLikeThisMaxQueryTerms :: Maybe MaxQueryTerms
- moreLikeThisStopWords :: Maybe [StopWord]
- moreLikeThisMinDocFrequency :: Maybe MinDocFrequency
- moreLikeThisMaxDocFrequency :: Maybe MaxDocFrequency
- moreLikeThisMinWordLength :: Maybe MinWordLength
- moreLikeThisMaxWordLength :: Maybe MaxWordLength
- moreLikeThisBoostTerms :: Maybe BoostTerms
- moreLikeThisBoost :: Maybe Boost
- moreLikeThisAnalyzer :: Maybe Analyzer
- data MoreLikeThisFieldQuery = MoreLikeThisFieldQuery {
- moreLikeThisFieldText :: Text
- moreLikeThisFieldFields :: FieldName
- moreLikeThisFieldPercentMatch :: Maybe PercentMatch
- moreLikeThisFieldMinimumTermFreq :: Maybe MinimumTermFrequency
- moreLikeThisFieldMaxQueryTerms :: Maybe MaxQueryTerms
- moreLikeThisFieldStopWords :: Maybe [StopWord]
- moreLikeThisFieldMinDocFrequency :: Maybe MinDocFrequency
- moreLikeThisFieldMaxDocFrequency :: Maybe MaxDocFrequency
- moreLikeThisFieldMinWordLength :: Maybe MinWordLength
- moreLikeThisFieldMaxWordLength :: Maybe MaxWordLength
- moreLikeThisFieldBoostTerms :: Maybe BoostTerms
- moreLikeThisFieldBoost :: Maybe Boost
- moreLikeThisFieldAnalyzer :: Maybe Analyzer
- data NestedQuery = NestedQuery {}
- data PrefixQuery = PrefixQuery {}
- data QueryStringQuery = QueryStringQuery {
- queryStringQuery :: QueryString
- queryStringDefaultField :: Maybe FieldName
- queryStringOperator :: Maybe BooleanOperator
- queryStringAnalyzer :: Maybe Analyzer
- queryStringAllowLeadingWildcard :: Maybe AllowLeadingWildcard
- queryStringLowercaseExpanded :: Maybe LowercaseExpanded
- queryStringEnablePositionIncrements :: Maybe EnablePositionIncrements
- queryStringFuzzyMaxExpansions :: Maybe MaxExpansions
- queryStringFuzziness :: Maybe Fuzziness
- queryStringFuzzyPrefixLength :: Maybe PrefixLength
- queryStringPhraseSlop :: Maybe PhraseSlop
- queryStringBoost :: Maybe Boost
- queryStringAnalyzeWildcard :: Maybe AnalyzeWildcard
- queryStringGeneratePhraseQueries :: Maybe GeneratePhraseQueries
- queryStringMinimumShouldMatch :: Maybe MinimumMatch
- queryStringLenient :: Maybe Lenient
- queryStringLocale :: Maybe Locale
- data SimpleQueryStringQuery = SimpleQueryStringQuery {
- simpleQueryStringQuery :: QueryString
- simpleQueryStringField :: Maybe FieldOrFields
- simpleQueryStringOperator :: Maybe BooleanOperator
- simpleQueryStringAnalyzer :: Maybe Analyzer
- simpleQueryStringFlags :: Maybe [SimpleQueryFlag]
- simpleQueryStringLowercaseExpanded :: Maybe LowercaseExpanded
- simpleQueryStringLocale :: Maybe Locale
- data RangeQuery = RangeQuery {}
- data RegexpQuery = RegexpQuery {}
- newtype QueryString = QueryString Text
- data BooleanOperator
- data ZeroTermsQuery
- newtype CutoffFrequency = CutoffFrequency Double
- newtype Analyzer = Analyzer Text
- newtype MaxExpansions = MaxExpansions Int
- newtype Lenient = Lenient Bool
- data MatchQueryType
- data MultiMatchQueryType
- newtype Tiebreaker = Tiebreaker Double
- newtype MinimumMatch = MinimumMatch Int
- newtype DisableCoord = DisableCoord Bool
- data CommonMinimumMatch
- data MinimumMatchHighLow = MinimumMatchHighLow {}
- newtype PrefixLength = PrefixLength Int
- newtype Fuzziness = Fuzziness Double
- newtype IgnoreTermFrequency = IgnoreTermFrequency Bool
- newtype MaxQueryTerms = MaxQueryTerms Int
- data ScoreType
- type Score = Maybe Double
- type Cache = Bool
- newtype TypeName = TypeName Text
- newtype BoostTerms = BoostTerms Double
- newtype MaxWordLength = MaxWordLength Int
- newtype MinWordLength = MinWordLength Int
- newtype MaxDocFrequency = MaxDocFrequency Int
- newtype MinDocFrequency = MinDocFrequency Int
- newtype PhraseSlop = PhraseSlop Int
- newtype StopWord = StopWord Text
- newtype QueryPath = QueryPath Text
- newtype MinimumTermFrequency = MinimumTermFrequency Int
- newtype PercentMatch = PercentMatch Double
- data FieldDefinition = FieldDefinition {
- fieldType :: FieldType
- data MappingField = MappingField {}
- data Mapping = Mapping {}
- newtype AllowLeadingWildcard = AllowLeadingWildcard Bool
- newtype LowercaseExpanded = LowercaseExpanded Bool
- newtype GeneratePhraseQueries = GeneratePhraseQueries Bool
- newtype Locale = Locale Text
- newtype AnalyzeWildcard = AnalyzeWildcard Bool
- newtype EnablePositionIncrements = EnablePositionIncrements Bool
- data SimpleQueryFlag
- data FieldOrFields
- class Monoid a where
- class ToJSON a where
- toJSON :: a -> Value
- data Interval
- data TimeInterval
- data ExecutionHint
- data CollectionMode
- data TermOrder = TermOrder {
- termSortField :: Text
- termSortOrder :: SortOrder
- data TermInclusion
- = TermInclusion Text
- | TermPattern Text Text
- data Aggregation
- type Aggregations = Map Text Aggregation
- type AggregationResults = Map Text Value
- data Bucket a = Bucket {
- buckets :: [a]
- class BucketAggregation a where
- data TermsAggregation = TermsAggregation {
- term :: Either Text Text
- termInclude :: Maybe TermInclusion
- termExclude :: Maybe TermInclusion
- termOrder :: Maybe TermOrder
- termMinDocCount :: Maybe Int
- termSize :: Maybe Int
- termShardSize :: Maybe Int
- termCollectMode :: Maybe CollectionMode
- termExecutionHint :: Maybe ExecutionHint
- termAggs :: Maybe Aggregations
- data DateHistogramAggregation = DateHistogramAggregation {
- dateField :: FieldName
- dateInterval :: Interval
- dateFormat :: Maybe Text
- datePreZone :: Maybe Text
- datePostZone :: Maybe Text
- datePreOffset :: Maybe Text
- datePostOffset :: Maybe Text
- dateAggs :: Maybe Aggregations
- data Highlights = Highlights {}
- data FieldHighlight = FieldHighlight FieldName (Maybe HighlightSettings)
- data HighlightSettings
- data PlainHighlight = PlainHighlight {}
- data PostingsHighlight = PostingsHighlight (Maybe CommonHighlight)
- data FastVectorHighlight = FastVectorHighlight {
- fvCommon :: Maybe CommonHighlight
- fvNonPostSettings :: Maybe NonPostings
- boundaryChars :: Maybe Text
- boundaryMaxScan :: Maybe Int
- fragmentOffset :: Maybe Int
- matchedFields :: [Text]
- phraseLimit :: Maybe Int
- data CommonHighlight = CommonHighlight {
- order :: Maybe Text
- forceSource :: Maybe Bool
- tag :: Maybe HighlightTag
- encoder :: Maybe HighlightEncoder
- noMatchSize :: Maybe Int
- highlightQuery :: Maybe Query
- requireFieldMatch :: Maybe Bool
- data NonPostings = NonPostings {}
- data HighlightEncoder
- data HighlightTag
- = TagSchema Text
- | CustomTags ([Text], [Text])
- type HitHighlight = Map Text [Text]
- data TermsResult = TermsResult {
- termKey :: Text
- termsDocCount :: Int
- termsAggs :: Maybe AggregationResults
- data DateHistogramResult = DateHistogramResult {
- dateKey :: Int
- dateKeyStr :: Maybe Text
- dateDocCount :: Int
- dateHistogramAggs :: Maybe AggregationResults
Documentation
defaultIndexSettings :: IndexSettings Source
defaultIndexSettings
is an IndexSettings
with 3 shards and 2 replicas.
defaultIndexDocumentSettings :: IndexDocumentSettings Source
Reasonable default settings. Chooses no version control.
mkSort :: FieldName -> SortOrder -> DefaultSort Source
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 FieldName
s and QueryString
to
make a MultiMatchQuery
.
mkRangeQuery :: FieldName -> RangeValue -> RangeQuery Source
mkAggregations :: Text -> Aggregation -> Aggregations Source
mkTermsAggregation :: Text -> TermsAggregation Source
mkTermsScriptAggregation :: Text -> TermsAggregation Source
mkDocVersion :: Int -> Maybe DocVersion Source
Smart constructor for in-range doc version
docVersionNumber :: DocVersion -> Int Source
toTerms :: Text -> AggregationResults -> Maybe (Bucket TermsResult) Source
toDateHistogram :: Text -> AggregationResults -> Maybe (Bucket DateHistogramResult) Source
Instances
MonadTrans BH | |
MonadError e m => MonadError e (BH m) | |
MonadReader r m => MonadReader r (BH m) | |
MonadState s m => MonadState s (BH m) | |
MonadWriter w m => MonadWriter w (BH m) | |
Alternative m => Alternative (BH m) | |
Monad m => Monad (BH m) | |
Functor m => Functor (BH m) | |
MonadFix m => MonadFix (BH m) | |
MonadPlus m => MonadPlus (BH m) | |
Applicative m => Applicative (BH m) | |
MonadIO m => MonadIO (BH m) | |
(Functor m, Applicative m, MonadIO m) => MonadBH (BH m) |
Common environment for Elasticsearch calls. Connections will be pipelined according to the provided HTTP connection manager.
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.
Constructors
Version | |
Fields
|
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.
Constructors
Status | |
data IndexSettings Source
IndexSettings
is used to configure the shards and replicas when you create
an Elasticsearch Index.
http://www.elasticsearch.org/guide/en/elasticsearch/reference/current/indices-create-index.html
Constructors
IndexSettings | |
Fields |
Instances
EsResult
describes the standard wrapper JSON document that you see in
successful Elasticsearch responses.
Constructors
EsResult | |
data DocVersion Source
DocVersion
is an integer version number for a document between 1
and 9.2e+18 used for .
Instances
newtype ExternalDocVersion Source
ExternalDocVersion
is a convenience wrapper if your code uses its
own version numbers instead of ones from ES.
Constructors
ExternalDocVersion DocVersion |
data VersionControl Source
VersionControl
is specified when indexing documents as a
optimistic concurrency control.
Constructors
NoVersionControl | Don't send a version. This is a pure overwrite. |
InternalVersion DocVersion | Use the default ES versioning scheme. Only index the document if the version is the same as the one specified. Only applicable to updates, as you should be getting Version from a search result. |
ExternalGT ExternalDocVersion | Use your own version numbering. Only index the document if the version is strictly higher OR the document doesn't exist. The given version will be used as the new version number for the stored document. N.B. All updates must increment this number, meaning there is some global, external ordering of updates. |
ExternalGTE ExternalDocVersion | Use your own version numbering. Only index the document if the version is equal or higher than the stored version. Will succeed if there is no existing document. The given version will be used as the new version number for the stored document. Use with care, as this could result in data loss. |
ForceVersion ExternalDocVersion | The document will always be indexed and the given version will be the new version. This is typically used for correcting errors. Use with care, as this could result in data loss. |
Instances
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
Constructors
IndexDocumentSettings | |
Fields |
Constructors
Constructors
Search | |
Fields
|
data SearchResult a Source
Constructors
SearchResult | |
Fields
|
Instances
Eq a => Eq (SearchResult a) | |
Show a => Show (SearchResult a) | |
FromJSON a => FromJSON (SearchResult a) |
data SearchHits a Source
Instances
Eq a => Eq (SearchHits a) | |
Show a => Show (SearchHits a) | |
Monoid (SearchHits a) | |
FromJSON a => FromJSON (SearchHits a) |
type TrackSortScores = Bool Source
data ShardResult Source
Constructors
ShardResult | |
Fields
|
Instances
Eq ShardResult | |
Show ShardResult | |
Generic ShardResult | |
FromJSON ShardResult | |
type Rep ShardResult |
Constructors
Hit | |
Fields
|
Constructors
Constructors
MustMatch Term Cache | |
MustNotMatch Term Cache | |
ShouldMatch [Term] Cache |
data GeoBoundingBoxConstraint Source
Constructors
GeoBoundingBoxConstraint | |
Fields |
data GeoBoundingBox Source
Constructors
GeoBoundingBox | |
Fields
|
Instances
Constructors
Distance | |
Fields
|
data DistanceUnit Source
Constructors
Miles | |
Yards | |
Feet | |
Inches | |
Kilometers | |
Meters | |
Centimeters | |
Millimeters | |
NauticalMiles |
Instances
data DistanceType Source
Instances
data RangeValue Source
Constructors
Instances
data RegexpFlags Source
Constructors
AllRegexpFlags | |
NoRegexpFlags | |
SomeRegexpFlags (NonEmpty RegexpFlag) |
Instances
data RegexpFlag Source
Constructors
AnyString | |
Automaton | |
Complement | |
Empty | |
Intersection | |
Interval |
Instances
FieldName
is used all over the place wherever a specific field within
a document needs to be specified, usually in Query
s or Filter
s.
Constructors
FieldName Text |
newtype MappingName Source
MappingName
is part of mappings which are how ES describes and schematizes
the data in the indices.
Constructors
MappingName Text |
Instances
Eq MappingName | |
Show MappingName | |
Generic MappingName | |
ToJSON MappingName | |
FromJSON MappingName | |
type Rep MappingName |
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 |
CacheName
is used in RegexpFilter
for describing the
CacheKey
keyed caching behavior.
Constructors
CacheName Text |
CacheKey
is used in RegexpFilter
to key regex caching.
Constructors
CacheKey Text |
data BulkOperation Source
BulkOperation
is a sum type for expressing the four kinds of bulk
operation index, create, delete, and update. BulkIndex
behaves like an
"upsert", BulkCreate
will fail if a document already exists at the DocId.
http://www.elasticsearch.org/guide/en/elasticsearch/reference/current/docs-bulk.html#docs-bulk
Constructors
BulkIndex IndexName MappingName DocId Value | |
BulkCreate IndexName MappingName DocId Value | |
BulkDelete IndexName MappingName DocId | |
BulkUpdate IndexName MappingName DocId Value |
Instances
newtype ReplicaCount Source
ReplicaCount
is part of IndexSettings
Constructors
ReplicaCount Int |
Instances
SortMode
prescribes how to handle sorting array/multi-valued fields.
SortOrder
is Ascending
or Descending
, as you might expect. These get
encoded into "asc" or "desc" when turned into JSON.
Constructors
Ascending | |
Descending |
The two main kinds of SortSpec
are DefaultSortSpec
and
GeoDistanceSortSpec
. The latter takes a SortOrder
, GeoPoint
, and
DistanceUnit
to express "nearness" to a single geographical point as a
sort specification.
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.
Constructors
DefaultSort | |
Fields
|
Instances
Missing
prescribes how to handle missing fields. A missing field can be
sorted last, first, or using a custom value as a substitute.
Constructors
LastMissing | |
FirstMissing | |
CustomMissing Text |
data OpenCloseIndex Source
OpenCloseIndex
is a sum type for opening and closing indices.
http://www.elasticsearch.org/guide/en/elasticsearch/reference/current/indices-open-close.html
Constructors
OpenIndex | |
CloseIndex |
Instances
data MatchQuery Source
Constructors
Instances
data MultiMatchQuery Source
Constructors
Constructors
BoolQuery | |
data BoostingQuery Source
Constructors
BoostingQuery | |
Fields
|
Instances
data CommonTermsQuery Source
Constructors
data DisMaxQuery Source
Constructors
DisMaxQuery | |
Fields
|
Instances
data FuzzyLikeThisQuery Source
Constructors
FuzzyLikeThisQuery | |
data FuzzyLikeFieldQuery Source
Constructors
data MoreLikeThisQuery Source
Constructors
data MoreLikeThisFieldQuery Source
Constructors
data PrefixQuery Source
Constructors
PrefixQuery | |
Fields
|
Instances
data QueryStringQuery Source
Constructors
data SimpleQueryStringQuery Source
Constructors
newtype QueryString Source
QueryString
is used to wrap query text bodies, be they human written or not.
Constructors
QueryString Text |
Instances
data BooleanOperator Source
BooleanOperator
is the usual And/Or operators with an ES compatible
JSON encoding baked in. Used all over the place.
newtype CutoffFrequency Source
Constructors
CutoffFrequency Double |
Constructors
Analyzer Text |
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.
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 |
Instances
data CommonMinimumMatch Source
newtype PrefixLength Source
PrefixLength
is the prefix length used in queries, defaults to 0.
Constructors
PrefixLength Int |
Instances
newtype IgnoreTermFrequency Source
Constructors
IgnoreTermFrequency Bool |
Constructors
ScoreTypeMax | |
ScoreTypeSum | |
ScoreTypeAvg | |
ScoreTypeNone |
Constructors
TypeName Text |
newtype MaxDocFrequency Source
Constructors
MaxDocFrequency Int |
newtype MinDocFrequency Source
Constructors
MinDocFrequency Int |
newtype PhraseSlop Source
PhraseSlop
sets the default slop for phrases, 0 means exact
phrase matches. Default is 0.
Constructors
PhraseSlop Int |
Instances
Constructors
StopWord Text |
Constructors
QueryPath Text |
newtype MinimumTermFrequency Source
Constructors
MinimumTermFrequency Int |
Support for type reification of Mapping
s is currently incomplete, for
now the mapping API verbiage expects a ToJSON
able 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 | |
Fields
|
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.
Constructors
AllowLeadingWildcard Bool |
newtype LowercaseExpanded Source
Constructors
LowercaseExpanded Bool |
newtype GeneratePhraseQueries Source
GeneratePhraseQueries
defaults to false.
Constructors
GeneratePhraseQueries Bool |
newtype AnalyzeWildcard Source
By default, wildcard terms in a query are not analyzed.
Setting AnalyzeWildcard
to true enables best-effort analysis.
Constructors
AnalyzeWildcard Bool |
newtype EnablePositionIncrements Source
Constructors
EnablePositionIncrements Bool |
data SimpleQueryFlag Source
data FieldOrFields Source
Instances
class Monoid a where
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:
mappend mempty x = x
mappend x mempty = x
mappend x (mappend y z) = mappend (mappend x y) z
mconcat =
foldr
mappend mempty
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Minimal complete definition: mempty
and mappend
.
Some types can be viewed as a monoid in more than one way,
e.g. both addition and multiplication on numbers.
In such cases we often define newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
Methods
mempty :: a
Identity of mappend
mappend :: a -> a -> a
An associative operation
mconcat :: [a] -> a
Fold a list using the monoid.
For most types, the default definition for mconcat
will be
used, but the function is included in the class definition so
that an optimized version can be provided for specific types.
Instances
Monoid Ordering | |
Monoid () | |
Monoid All | |
Monoid Any | |
Monoid ByteString | |
Monoid ByteString | |
Monoid Builder | |
Monoid IntSet | |
Monoid More | |
Monoid Text | |
Monoid RequestBody | |
Monoid CookieJar | |
Monoid Buffer | |
Monoid Text | |
Monoid Buffer | |
Monoid Filter | |
Monoid Query | |
Monoid [a] | |
Monoid a => Monoid (Dual a) | |
Monoid (Endo a) | |
Num a => Monoid (Sum a) | |
Num a => Monoid (Product a) | |
Monoid (First a) | |
Monoid (Last a) | |
Monoid a => Monoid (Maybe a) | Lift a semigroup into |
Monoid (IntMap a) | |
Ord a => Monoid (Set a) | |
Monoid (Seq a) | |
Monoid (Result a) | |
Monoid (Parser a) | |
Monoid (Vector a) | |
Monoid (DList a) | |
Storable a => Monoid (Vector a) | |
Prim a => Monoid (Vector a) | |
Unbox a => Monoid (Vector a) | |
(Hashable a, Eq a) => Monoid (HashSet a) | |
Monoid (SearchHits a) | |
Monoid b => Monoid (a -> b) | |
(Monoid a, Monoid b) => Monoid (a, b) | |
Monoid a => Monoid (Const a b) | |
Monoid (Proxy * s) | |
Ord k => Monoid (Map k v) | |
Monoid (Parser i a) | |
(Eq k, Hashable k) => Monoid (HashMap k v) | |
Monoid (Parser' e a) | |
Typeable (* -> Constraint) Monoid | |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) |
class ToJSON a where
Minimal complete definition
Nothing
Methods
toJSON :: a -> Value
Instances
data TimeInterval Source
Instances
data ExecutionHint Source
Instances
Constructors
TermOrder | |
Fields
|
data Aggregation Source
Instances
type Aggregations = Map Text Aggregation Source
type AggregationResults = Map Text Value Source
Instances
Show a => Show (Bucket a) | |
(FromJSON a, BucketAggregation a) => FromJSON (Bucket a) |
class BucketAggregation a where Source
Methods
aggs :: a -> Maybe AggregationResults Source
data TermsAggregation Source
Constructors
TermsAggregation | |
Fields
|
Instances
data DateHistogramAggregation Source
Constructors
DateHistogramAggregation | |
Fields
|
data HighlightSettings Source
data FastVectorHighlight Source
Constructors
FastVectorHighlight | |
Fields
|
Instances
data CommonHighlight Source
Constructors
CommonHighlight | |
Fields
|
Instances
data HighlightEncoder Source
Constructors
DefaultEncoder | |
HTMLEncoder |
type HitHighlight = Map Text [Text] Source
data TermsResult Source
Constructors
TermsResult | |
Fields
|
Instances
data DateHistogramResult Source
Constructors
DateHistogramResult | |
Fields
|
Instances