Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type Aggregations = Map Text Aggregation
- emptyAggregations :: Aggregations
- mkAggregations :: Text -> Aggregation -> Aggregations
- data Aggregation
- data TopHitsAggregation = TopHitsAggregation {}
- data MissingAggregation = MissingAggregation {}
- 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 CardinalityAggregation = CardinalityAggregation {}
- data DateHistogramAggregation = DateHistogramAggregation {}
- data DateRangeAggregation = DateRangeAggregation {}
- data DateRangeAggRange
- data ValueCountAggregation
- data FilterAggregation = FilterAggregation {}
- mkTermsAggregation :: Text -> TermsAggregation
- mkTermsScriptAggregation :: Text -> TermsAggregation
- mkDateHistogram :: FieldName -> Interval -> DateHistogramAggregation
- mkCardinalityAggregation :: FieldName -> CardinalityAggregation
- data TermInclusion
- data TermOrder = TermOrder {}
- data ExecutionHint
- data DateMathExpr = DateMathExpr DateMathAnchor [DateMathModifier]
- data DateMathAnchor
- data DateMathModifier
- data DateMathUnit
- data CollectionMode
- type AggregationResults = Map Text Value
- class BucketAggregation a where
- data BucketValue
- data Bucket a = Bucket {
- buckets :: [a]
- data TermsResult = TermsResult {}
- data DateHistogramResult = DateHistogramResult {}
- data DateRangeResult = DateRangeResult {}
- toTerms :: Text -> AggregationResults -> Maybe (Bucket TermsResult)
- toDateHistogram :: Text -> AggregationResults -> Maybe (Bucket DateHistogramResult)
- toMissing :: Text -> AggregationResults -> Maybe MissingResult
- toTopHits :: FromJSON a => Text -> AggregationResults -> Maybe (TopHitResult a)
- toAggResult :: FromJSON a => Text -> AggregationResults -> Maybe a
- data MissingResult = MissingResult {}
- data TopHitResult a = TopHitResult {
- tarHits :: SearchHits a
- data SearchHits a = SearchHits {}
- data Hit a = Hit {
- hitIndex :: IndexName
- hitType :: MappingName
- hitDocId :: DocId
- hitScore :: Score
- hitSource :: Maybe a
- hitHighlight :: Maybe HitHighlight
- getNamedSubAgg :: Object -> [Text] -> Maybe AggregationResults
Documentation
type Aggregations = Map Text Aggregation Source #
mkAggregations :: Text -> Aggregation -> Aggregations Source #
data Aggregation Source #
data TopHitsAggregation Source #
data MissingAggregation Source #
data TermsAggregation Source #
data DateRangeAggRange Source #
data ValueCountAggregation Source #
data FilterAggregation Source #
Single-bucket filter aggregations. See https://www.elastic.co/guide/en/elasticsearch/reference/current/search-aggregations-bucket-filter-aggregation.html#search-aggregations-bucket-filter-aggregation for more information.
data TermInclusion Source #
data ExecutionHint Source #
data DateMathExpr Source #
See https://www.elastic.co/guide/en/elasticsearch/reference/current/common-options.html#date-math for more information.
data DateMathAnchor Source #
Starting point for a date range. This along with the DateMathModifiers
gets you the date ES will start from.
data DateMathModifier Source #
data DateMathUnit Source #
data CollectionMode Source #
class BucketAggregation a where Source #
key :: a -> BucketValue Source #
aggs :: a -> Maybe AggregationResults Source #
data BucketValue Source #
data TermsResult Source #
data DateHistogramResult Source #
toTerms :: Text -> AggregationResults -> Maybe (Bucket TermsResult) Source #
toMissing :: Text -> AggregationResults -> Maybe MissingResult Source #
toTopHits :: FromJSON a => Text -> AggregationResults -> Maybe (TopHitResult a) Source #
toAggResult :: FromJSON a => Text -> AggregationResults -> Maybe a Source #
data MissingResult Source #
data TopHitResult a Source #
Show a => Show (TopHitResult a) Source # | |
FromJSON a => FromJSON (TopHitResult a) Source # | |
data SearchHits a Source #
Eq a => Eq (SearchHits a) Source # | |
Show a => Show (SearchHits a) Source # | |
Semigroup (SearchHits a) Source # | |
Monoid (SearchHits a) Source # | |
FromJSON a => FromJSON (SearchHits a) Source # | |
Hit | |
|
getNamedSubAgg :: Object -> [Text] -> Maybe AggregationResults Source #