| 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 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.
- defaultCache :: Cache
- defaultIndexSettings :: IndexSettings
- halfRangeToKV :: HalfRange -> (Text, Double)
- mkSort :: FieldName -> SortOrder -> DefaultSort
- rangeToKV :: Range -> (Text, Double, Text, Double)
- showText :: Show a => a -> Text
- unpackId :: DocId -> String
- mkMatchQuery :: FieldName -> QueryString -> MatchQuery
- mkMultiMatchQuery :: [FieldName] -> QueryString -> MultiMatchQuery
- mkBoolQuery :: [Query] -> [Query] -> [Query] -> BoolQuery
- mkRangeQuery :: FieldName -> Either HalfRange Range -> RangeQuery
- mkQueryStringQuery :: QueryString -> QueryStringQuery
- mkAggregations :: Text -> Aggregation -> Aggregations
- mkTermsAggregation :: Text -> TermsAggregation
- mkTermsScriptAggregation :: Text -> TermsAggregation
- mkDateHistogram :: FieldName -> Interval -> DateHistogramAggregation
- toTerms :: Text -> AggregationResults -> Maybe (Bucket TermsResult)
- toDateHistogram :: Text -> AggregationResults -> Maybe (Bucket DateHistogramResult)
- omitNulls :: [(Text, Value)] -> Value
- data Version = Version {}
- data Status = Status {}
- newtype Existence = Existence Bool
- newtype NullValue = NullValue Bool
- data IndexSettings = IndexSettings {}
- newtype Server = Server String
- type Reply = Response ByteString
- data EsResult a = EsResult {}
- data Query
- = TermQuery Term (Maybe Boost)
- | TermsQuery [Term] MinimumMatch
- | 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 {
- queryBody :: Maybe Query
- filterBody :: Maybe Filter
- sortBody :: Maybe Sort
- aggBody :: Maybe Aggregations
- highlight :: Maybe Highlights
- trackSortScores :: TrackSortScores
- from :: From
- size :: Size
- data FromJSON a => SearchResult a = SearchResult {
- took :: Int
- timedOut :: Bool
- shards :: ShardResult
- searchHits :: SearchHits a
- aggregations :: Maybe AggregationResults
- data FromJSON a => SearchHits a = SearchHits {}
- data ShardResult = ShardResult {
- shardTotal :: Int
- shardsSuccessful :: Int
- shardsFailed :: Int
- data FromJSON a => 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
- | RangeFilter FieldName (Either HalfRange Range) RangeExecution Cache
- | RegexpFilter FieldName Regexp RegexpFlags CacheName Cache CacheKey
- | TermFilter Term Cache
- class Monoid a => Seminearring a where
- data BoolMatch
- = MustMatch Term Cache
- | MustNotMatch Term Cache
- | ShouldMatch [Term] Cache
- data Term = Term {}
- data GeoPoint = GeoPoint {}
- data GeoBoundingBoxConstraint = GeoBoundingBoxConstraint {
- geoBBField :: FieldName
- constraintBox :: GeoBoundingBox
- bbConstraintcache :: Cache
- geoType :: GeoFilterType
- 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 Range
- data HalfRange
- data RangeExecution
- newtype LessThan = LessThan Double
- newtype LessThanEq = LessThanEq Double
- newtype GreaterThan = GreaterThan Double
- newtype GreaterThanEq = GreaterThanEq Double
- newtype Regexp = Regexp Text
- data RegexpFlags
- data RegexpFlag
- newtype FieldName = FieldName Text
- newtype IndexName = IndexName String
- newtype MappingName = MappingName String
- newtype DocId = DocId String
- newtype CacheName = CacheName Text
- newtype CacheKey = CacheKey Text
- data BulkOperation
- newtype ReplicaCount = ReplicaCount Int
- newtype ShardCount = ShardCount Int
- type Sort = [SortSpec]
- data SortMode
- data SortOrder
- data SortSpec
- data DefaultSort = DefaultSort {}
- data Missing
- 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
- 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
- data Interval
- data TimeInterval
- data ExecutionHint
- data CollectionMode
- data TermOrder = TermOrder {}
- data TermInclusion
- data Aggregation
- type Aggregations = Map Text Aggregation
- type AggregationResults = Map Text Value
- data (FromJSON a, BucketAggregation a) => 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 {}
- data Highlights = Highlights {}
- data FieldHighlight = FieldHighlight FieldName (Maybe HighlightSettings)
- data HighlightSettings
- data PlainHighlight = PlainHighlight {}
- data PostingsHighlight = PostingsHighlight (Maybe CommonHighlight)
- data FastVectorHighlight = FastVectorHighlight {}
- data CommonHighlight = CommonHighlight {}
- data NonPostings = NonPostings {}
- data HighlightEncoder
- data HighlightTag
- = TagSchema Text
- | CustomTags ([Text], [Text])
- type HitHighlight = Map Text [Text]
- data TermsResult = TermsResult {}
- data DateHistogramResult = DateHistogramResult {}
Documentation
defaultCache :: Cache Source
defaultIndexSettings :: IndexSettings Source
defaultIndexSettings is an IndexSettings with 3 shards and 2 replicas.
halfRangeToKV :: HalfRange -> (Text, Double) Source
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 FieldNames and QueryString to
make a MultiMatchQuery.
mkRangeQuery :: FieldName -> Either HalfRange Range -> RangeQuery Source
mkAggregations :: Text -> Aggregation -> Aggregations Source
toTerms :: Text -> AggregationResults -> Maybe (Bucket TermsResult) Source
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
Server is used with the client functions to point at the ES instance
EsResult describes the standard wrapper JSON document that you see in
successful Elasticsearch responses.
Constructors
| EsResult | |
Constructors
Constructors
| Search | |
Fields
| |
data FromJSON a => SearchResult a Source
Constructors
| SearchResult | |
Fields
| |
Instances
| (Eq a, FromJSON a) => Eq (SearchResult a) | |
| (Show a, FromJSON a) => Show (SearchResult a) | |
| FromJSON a => FromJSON (SearchResult a) |
data FromJSON a => SearchHits a Source
Instances
| (Eq a, FromJSON a) => Eq (SearchHits a) | |
| (Show a, FromJSON a) => Show (SearchHits a) | |
| FromJSON a => FromJSON (SearchHits a) |
data ShardResult Source
Constructors
| ShardResult | |
Fields
| |
Instances
data FromJSON a => Hit a Source
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 RegexpFlags Source
Constructors
| AllRegexpFlags | |
| NoRegexpFlags | |
| SomeRegexpFlags (NonEmpty RegexpFlag) |
Instances
data RegexpFlag Source
Constructors
| AnyString | |
| Automaton | |
| Complement | |
| Empty | |
| Intersection | |
| Interval |
Instances
IndexName is used to describe which index to querycreatedelete
newtype MappingName Source
MappingName is part of mappings which are how ES describes and schematizes
the data in the indices.
Constructors
| MappingName String |
Instances
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.
CacheName is used in RegexpFilter for describing the
CacheKey keyed caching behavior.
CacheKey is used in RegexpFilter to key regex caching.
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 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 |
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 |
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
newtype MinimumTermFrequency Source
Constructors
| MinimumTermFrequency Int |
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 | |
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 |
Locale is used for string conversions - defaults to ROOT.
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 =
foldrmappend 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 newtypes 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
class ToJSON a where
A type that can be converted to JSON.
An example type and instance:
@{-# LANGUAGE OverloadedStrings #-}
data Coord = Coord { x :: Double, y :: Double }
instance ToJSON Coord where
toJSON (Coord x y) = object ["x" .= x, "y" .= y]
@
Note the use of the OverloadedStrings language extension which enables
Text values to be written as string literals.
Instead of manually writing your ToJSON instance, there are three options
to do it automatically:
- Data.Aeson.TH provides template-haskell functions which will derive an instance at compile-time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
- Data.Aeson.Generic provides a generic
toJSONfunction that accepts any type which is an instance ofData. - If your compiler has support for the
DeriveGenericandDefaultSignatureslanguage extensions (GHC 7.2 and newer),toJSONwill have a default generic implementation.
To use the latter option, simply add a deriving clause to your
datatype and declare a GenericToJSON instance for your datatype without giving a
definition for toJSON.
For example the previous example can be simplified to just:
@{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics
data Coord = Coord { x :: Double, y :: Double } deriving Generic
instance ToJSON Coord @
Note that, instead of using DefaultSignatures, it's also possible
to parameterize the generic encoding using genericToJSON applied
to your encoding/decoding Options:
instance ToJSON Coord where
toJSON = genericToJSON defaultOptions
Minimal complete definition
Nothing
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
data (FromJSON a, BucketAggregation a) => Bucket a Source
Instances
| (Show a, FromJSON a, BucketAggregation 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
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
| |
data DateHistogramResult Source
Constructors
| DateHistogramResult | |
Fields
| |