Copyright | (C) 2014 2018 Chris Allen |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Chris Allen <cma@bitemyapp.com |
Stability | provisional |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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.
Synopsis
- newtype Bytes = Bytes Int
- data Interval
- data TimeInterval
- gigabytes :: Int -> Bytes
- kilobytes :: Int -> Bytes
- megabytes :: Int -> Bytes
- parseStringInterval :: (Monad m, MonadFail m) => String -> m NominalDiffTime
- data TaskResponse a = TaskResponse {}
- taskResponseCompletedLens :: Lens' (TaskResponse a) Bool
- taskResponseTaskLens :: Lens' (TaskResponse a) (Task a)
- taskResponseReponseLens :: Lens' (TaskResponse a) (Maybe a)
- taskResponseErrorLens :: Lens' (TaskResponse a) (Maybe Object)
- data Task a = Task {}
- newtype TaskNodeId = TaskNodeId Text
- taskNodeLens :: Lens' (Task a) Text
- taskIdLens :: Lens' (Task a) Int
- taskTypeLens :: Lens' (Task a) Text
- taskActionLens :: Lens' (Task a) Text
- taskStatusLens :: Lens' (Task a) a
- taskDescriptionLens :: Lens' (Task a) Text
- taskStartTimeInMillisLens :: Lens' (Task a) Integer
- taskRunningTimeInNanosLens :: Lens' (Task a) Integer
- taskCancellableLens :: Lens' (Task a) Bool
- data Suggest = Suggest {}
- suggestTextLens :: Lens' Suggest Text
- suggestNameLens :: Lens' Suggest Text
- suggestTypeLens :: Lens' Suggest SuggestType
- data SuggestType = SuggestTypePhraseSuggester PhraseSuggester
- data PhraseSuggester = PhraseSuggester {
- phraseSuggesterField :: FieldName
- phraseSuggesterGramSize :: Maybe Int
- phraseSuggesterRealWordErrorLikelihood :: Maybe Int
- phraseSuggesterConfidence :: Maybe Int
- phraseSuggesterMaxErrors :: Maybe Int
- phraseSuggesterSeparator :: Maybe Text
- phraseSuggesterSize :: Maybe Size
- phraseSuggesterAnalyzer :: Maybe Analyzer
- phraseSuggesterShardSize :: Maybe Int
- phraseSuggesterHighlight :: Maybe PhraseSuggesterHighlighter
- phraseSuggesterCollate :: Maybe PhraseSuggesterCollate
- phraseSuggesterCandidateGenerators :: [DirectGenerators]
- mkPhraseSuggester :: FieldName -> PhraseSuggester
- phraseSuggesterFieldLens :: Lens' PhraseSuggester FieldName
- phraseSuggesterGramSizeLens :: Lens' PhraseSuggester (Maybe Int)
- phraseSuggesterRealWordErrorLikelihoodLens :: Lens' PhraseSuggester (Maybe Int)
- phraseSuggesterConfidenceLens :: Lens' PhraseSuggester (Maybe Int)
- phraseSuggesterMaxErrorsLens :: Lens' PhraseSuggester (Maybe Int)
- phraseSuggesterSeparatorLens :: Lens' PhraseSuggester (Maybe Text)
- phraseSuggesterSizeLens :: Lens' PhraseSuggester (Maybe Size)
- phraseSuggesterAnalyzerLens :: Lens' PhraseSuggester (Maybe Analyzer)
- phraseSuggesterShardSizeLens :: Lens' PhraseSuggester (Maybe Int)
- phraseSuggesterHighlightLens :: Lens' PhraseSuggester (Maybe PhraseSuggesterHighlighter)
- phraseSuggesterCollateLens :: Lens' PhraseSuggester (Maybe PhraseSuggesterCollate)
- phraseSuggesterCandidateGeneratorsLens :: Lens' PhraseSuggester [DirectGenerators]
- data PhraseSuggesterHighlighter = PhraseSuggesterHighlighter {}
- phraseSuggesterHighlighterPreTagLens :: Lens' PhraseSuggesterHighlighter Text
- phraseSuggesterHighlighterPostTagLens :: Lens' PhraseSuggesterHighlighter Text
- data PhraseSuggesterCollate = PhraseSuggesterCollate {}
- phraseSuggesterCollateTemplateQueryLens :: Lens' PhraseSuggesterCollate Query
- phraseSuggesterCollateParamsLens :: Lens' PhraseSuggesterCollate TemplateQueryKeyValuePairs
- phraseSuggesterCollatePruneLens :: Lens' PhraseSuggesterCollate Bool
- data SuggestOptions = SuggestOptions {}
- suggestOptionsTextLens :: Lens' SuggestOptions Text
- suggestOptionsScoreLens :: Lens' SuggestOptions Double
- suggestOptionsFreqLens :: Lens' SuggestOptions (Maybe Int)
- suggestOptionsHighlightedLens :: Lens' SuggestOptions (Maybe Text)
- data SuggestResponse = SuggestResponse {}
- suggestResponseTextLens :: Lens' SuggestResponse Text
- suggestResponseOffsetLens :: Lens' SuggestResponse Int
- suggestResponseLengthLens :: Lens' SuggestResponse Int
- suggestResponseOptionsLens :: Lens' SuggestResponse [SuggestOptions]
- data NamedSuggestionResponse = NamedSuggestionResponse {
- nsrName :: Text
- nsrResponses :: [SuggestResponse]
- nsrNameLens :: Lens' NamedSuggestionResponse Text
- nsrResponsesLens :: Lens' NamedSuggestionResponse [SuggestResponse]
- data DirectGeneratorSuggestModeTypes
- data DirectGenerators = DirectGenerators {
- directGeneratorsField :: FieldName
- directGeneratorsSize :: Maybe Int
- directGeneratorSuggestMode :: DirectGeneratorSuggestModeTypes
- directGeneratorMaxEdits :: Maybe Double
- directGeneratorPrefixLength :: Maybe Int
- directGeneratorMinWordLength :: Maybe Int
- directGeneratorMaxInspections :: Maybe Int
- directGeneratorMinDocFreq :: Maybe Double
- directGeneratorMaxTermFreq :: Maybe Double
- directGeneratorPreFilter :: Maybe Text
- directGeneratorPostFilter :: Maybe Text
- mkDirectGenerators :: FieldName -> DirectGenerators
- directGeneratorsFieldLens :: Lens' DirectGenerators FieldName
- directGeneratorsSizeLens :: Lens' DirectGenerators (Maybe Int)
- directGeneratorSuggestModeLens :: Lens' DirectGenerators DirectGeneratorSuggestModeTypes
- directGeneratorMaxEditsLens :: Lens' DirectGenerators (Maybe Double)
- directGeneratorPrefixLengthLens :: Lens' DirectGenerators (Maybe Int)
- directGeneratorMinWordLengthLens :: Lens' DirectGenerators (Maybe Int)
- directGeneratorMaxInspectionsLens :: Lens' DirectGenerators (Maybe Int)
- directGeneratorMinDocFreqLens :: Lens' DirectGenerators (Maybe Double)
- directGeneratorMaxTermFreqLens :: Lens' DirectGenerators (Maybe Double)
- directGeneratorPreFilterLens :: Lens' DirectGenerators (Maybe Text)
- directGeneratorPostFilterLens :: Lens' DirectGenerators (Maybe Text)
- data SortMode
- mkSort :: FieldName -> SortOrder -> DefaultSort
- type Sort = [SortSpec]
- data SortSpec
- data DefaultSort = DefaultSort {}
- sortFieldNameLens :: Lens' DefaultSort FieldName
- sortOrderLens :: Lens' DefaultSort SortOrder
- ignoreUnmappedLens :: Lens' DefaultSort (Maybe Text)
- sortModeLens :: Lens' DefaultSort (Maybe SortMode)
- missingSortLens :: Lens' DefaultSort (Maybe Missing)
- nestedFilterLens :: Lens' DefaultSort (Maybe Filter)
- data SortOrder
- data Missing
- data FsSnapshotRepo = FsSnapshotRepo {}
- data GenericSnapshotRepo = GenericSnapshotRepo {}
- newtype GenericSnapshotRepoSettings = GenericSnapshotRepoSettings {}
- newtype RRGroupRefNum = RRGroupRefNum {
- rrGroupRefNum :: Int
- newtype RestoreIndexSettings = RestoreIndexSettings {}
- newtype RestoreRenamePattern = RestoreRenamePattern {}
- data RestoreRenameToken
- data SnapshotCreateSettings = SnapshotCreateSettings {}
- data SnapshotInfo = SnapshotInfo {}
- data SnapshotNodeVerification = SnapshotNodeVerification {}
- data SnapshotPattern
- class SnapshotRepo r where
- data SnapshotRepoConversionError
- newtype SnapshotRepoName = SnapshotRepoName {}
- data SnapshotRepoPattern
- data SnapshotRepoSelection
- newtype SnapshotRepoType = SnapshotRepoType {}
- newtype SnapshotRepoUpdateSettings = SnapshotRepoUpdateSettings {}
- data SnapshotRestoreSettings = SnapshotRestoreSettings {
- snapRestoreWaitForCompletion :: Bool
- snapRestoreIndices :: Maybe IndexSelection
- snapRestoreIgnoreUnavailable :: Bool
- snapRestoreIncludeGlobalState :: Bool
- snapRestoreRenamePattern :: Maybe RestoreRenamePattern
- snapRestoreRenameReplacement :: Maybe (NonEmpty RestoreRenameToken)
- snapRestorePartial :: Bool
- snapRestoreIncludeAliases :: Bool
- snapRestoreIndexSettingsOverrides :: Maybe RestoreIndexSettings
- snapRestoreIgnoreIndexSettings :: Maybe (NonEmpty Text)
- data SnapshotSelection
- data SnapshotShardFailure = SnapshotShardFailure {}
- data SnapshotState
- newtype SnapshotVerification = SnapshotVerification {}
- defaultSnapshotCreateSettings :: SnapshotCreateSettings
- defaultSnapshotRepoUpdateSettings :: SnapshotRepoUpdateSettings
- defaultSnapshotRestoreSettings :: SnapshotRestoreSettings
- mkRRGroupRefNum :: Int -> Maybe RRGroupRefNum
- snapshotRepoNameLens :: Lens' SnapshotRepoName Text
- gSnapshotRepoNameLens :: Lens' GenericSnapshotRepo SnapshotRepoName
- gSnapshotRepoTypeLens :: Lens' GenericSnapshotRepo SnapshotRepoType
- gSnapshotRepoSettingsLens :: Lens' GenericSnapshotRepo GenericSnapshotRepoSettings
- snapshotRepoTypeLens :: Lens' SnapshotRepoType Text
- gSnapshotRepoSettingsObjectLens :: Lens' GenericSnapshotRepoSettings Object
- snapshotNodeVerificationsLens :: Lens' SnapshotVerification [SnapshotNodeVerification]
- snvFullIdLens :: Lens' SnapshotNodeVerification FullNodeId
- snvNodeNameLens :: Lens' SnapshotNodeVerification NodeName
- snapRestoreWaitForCompletionLens :: Lens' SnapshotRestoreSettings Bool
- snapRestoreIndicesLens :: Lens' SnapshotRestoreSettings (Maybe IndexSelection)
- snapRestoreIgnoreUnavailableLens :: Lens' SnapshotRestoreSettings Bool
- snapRestoreIncludeGlobalStateLens :: Lens' SnapshotRestoreSettings Bool
- snapRestoreRenamePatternLens :: Lens' SnapshotRestoreSettings (Maybe RestoreRenamePattern)
- snapRestoreRenameReplacementLens :: Lens' SnapshotRestoreSettings (Maybe (NonEmpty RestoreRenameToken))
- snapRestorePartialLens :: Lens' SnapshotRestoreSettings Bool
- snapRestoreIncludeAliasesLens :: Lens' SnapshotRestoreSettings Bool
- snapRestoreIndexSettingsOverridesLens :: Lens' SnapshotRestoreSettings (Maybe RestoreIndexSettings)
- snapRestoreIgnoreIndexSettingsLens :: Lens' SnapshotRestoreSettings (Maybe (NonEmpty Text))
- repoUpdateVerifyLens :: Lens' SnapshotRepoUpdateSettings Bool
- fsrNameLens :: Lens' FsSnapshotRepo SnapshotRepoName
- fsrLocationLens :: Lens' FsSnapshotRepo FilePath
- fsrCompressMetadataLens :: Lens' FsSnapshotRepo Bool
- fsrChunkSizeLens :: Lens' FsSnapshotRepo (Maybe Bytes)
- fsrMaxRestoreBytesPerSecLens :: Lens' FsSnapshotRepo (Maybe Bytes)
- fsrMaxSnapshotBytesPerSecLens :: Lens' FsSnapshotRepo (Maybe Bytes)
- snapWaitForCompletionLens :: Lens' SnapshotCreateSettings Bool
- snapIndicesLens :: Lens' SnapshotCreateSettings (Maybe IndexSelection)
- snapIgnoreUnavailableLens :: Lens' SnapshotCreateSettings Bool
- snapIncludeGlobalStateLens :: Lens' SnapshotCreateSettings Bool
- snapPartialLens :: Lens' SnapshotCreateSettings Bool
- snapInfoShardsLens :: Lens' SnapshotInfo ShardResult
- snapInfoFailuresLens :: Lens' SnapshotInfo [SnapshotShardFailure]
- snapInfoDurationLens :: Lens' SnapshotInfo NominalDiffTime
- snapInfoEndTimeLens :: Lens' SnapshotInfo UTCTime
- snapInfoStartTimeLens :: Lens' SnapshotInfo UTCTime
- snapInfoStateLens :: Lens' SnapshotInfo SnapshotState
- snapInfoIndicesLens :: Lens' SnapshotInfo [IndexName]
- snapInfoNameLens :: Lens' SnapshotInfo SnapshotName
- snapShardFailureIndexLens :: Lens' SnapshotShardFailure IndexName
- snapShardFailureNodeIdLens :: Lens' SnapshotShardFailure (Maybe NodeName)
- snapShardFailureReasonLens :: Lens' SnapshotShardFailure Text
- snapShardFailureShardIdLens :: Lens' SnapshotShardFailure ShardId
- rrPatternLens :: Lens' RestoreRenamePattern Text
- restoreOverrideReplicasLens :: Lens' RestoreIndexSettings (Maybe ReplicaCount)
- data Exclude = Exclude [Pattern]
- data ExpandWildcards
- data GetTemplateScript = GetTemplateScript {}
- data Include = Include [Pattern]
- newtype Pattern = Pattern Text
- data PatternOrPatterns
- newtype ScrollId = ScrollId Text
- data Search = Search {
- queryBody :: Maybe Query
- filterBody :: Maybe Filter
- sortBody :: Maybe Sort
- aggBody :: Maybe Aggregations
- highlight :: Maybe Highlights
- trackSortScores :: TrackSortScores
- from :: From
- size :: Size
- searchType :: SearchType
- searchAfterKey :: Maybe SearchAfterKey
- fields :: Maybe [FieldName]
- scriptFields :: Maybe ScriptFields
- source :: Maybe Source
- suggestBody :: Maybe Suggest
- pointInTime :: Maybe PointInTime
- data SearchResult a = SearchResult {}
- data SearchTemplate = SearchTemplate {}
- newtype SearchTemplateId = SearchTemplateId Text
- newtype SearchTemplateSource = SearchTemplateSource Text
- data SearchType
- data Source
- data TimeUnits
- type TrackSortScores = Bool
- unpackId :: DocId -> Text
- tookLens :: Lens' (SearchResult a) Int
- timedOutLens :: Lens' (SearchResult a) Bool
- shardsLens :: Lens' (SearchResult a) ShardResult
- searchHitsLens :: Lens' (SearchResult a) (SearchHits a)
- aggregationsLens :: Lens' (SearchResult a) (Maybe AggregationResults)
- scrollIdLens :: Lens' (SearchResult a) (Maybe ScrollId)
- suggestLens :: Lens' (SearchResult a) (Maybe NamedSuggestionResponse)
- pitIdLens :: Lens' (SearchResult a) (Maybe Text)
- getTemplateScriptLangLens :: Lens' GetTemplateScript (Maybe Text)
- getTemplateScriptSourceLens :: Lens' GetTemplateScript (Maybe SearchTemplateSource)
- getTemplateScriptOptionsLens :: Lens' GetTemplateScript (Maybe (HashMap Text Text))
- getTemplateScriptIdLens :: Lens' GetTemplateScript Text
- getTemplateScriptFoundLens :: Lens' GetTemplateScript Bool
- data ReindexRequest = ReindexRequest {}
- reindexConflictsLens :: Lens' ReindexRequest (Maybe ReindexConflicts)
- reindexSourceLens :: Lens' ReindexRequest ReindexSource
- reindexDestLens :: Lens' ReindexRequest ReindexDest
- reindexScriptLens :: Lens' ReindexRequest (Maybe ReindexScript)
- data ReindexConflicts
- data ReindexSource = ReindexSource {}
- reindexSourceIndexLens :: Lens' ReindexSource (NonEmpty IndexName)
- reindexSourceMaxDocsLens :: Lens' ReindexSource (Maybe Int)
- reindexSourceQueryLens :: Lens' ReindexSource (Maybe Query)
- reindexSourceSizeLens :: Lens' ReindexSource (Maybe Int)
- reindexSourceSliceLens :: Lens' ReindexSource (Maybe ReindexSlice)
- data ReindexSlice = ReindexSlice {}
- reindexSliceIdLens :: Lens' ReindexSlice (Maybe Int)
- reindexSliceMaxLens :: Lens' ReindexSlice (Maybe Int)
- data ReindexDest = ReindexDest {}
- reindexDestIndexLens :: Lens' ReindexDest IndexName
- reindexDestVersionTypeLens :: Lens' ReindexDest (Maybe VersionType)
- reindexDestOpTypeLens :: Lens' ReindexDest (Maybe ReindexOpType)
- data VersionType
- data ReindexOpType
- data ReindexScript = ReindexScript {}
- reindexScriptLanguageLens :: Lens' ReindexScript ScriptLanguage
- reindexScriptSourceLens :: Lens' ReindexScript Text
- mkReindexRequest :: IndexName -> IndexName -> ReindexRequest
- data ReindexResponse = ReindexResponse {}
- reindexResponseTookLens :: Lens' ReindexResponse (Maybe Int)
- reindexResponseUpdatedLens :: Lens' ReindexResponse Int
- reindexResponseCreatedLens :: Lens' ReindexResponse Int
- reindexResponseBatchesLens :: Lens' ReindexResponse Int
- reindexResponseVersionConflictsLens :: Lens' ReindexResponse Int
- reindexResponseThrottledMillisLens :: Lens' ReindexResponse Int
- newtype ScriptFields = ScriptFields (KeyMap ScriptFieldValue)
- type ScriptFieldValue = Value
- data ScriptSource
- data Script = Script {}
- scriptLanguageLens :: Lens' Script (Maybe ScriptLanguage)
- scriptSourceLens :: Lens' Script ScriptSource
- scriptParamsLens :: Lens' Script (Maybe ScriptParams)
- newtype ScriptLanguage = ScriptLanguage Text
- newtype ScriptParams = ScriptParams (KeyMap ScriptParamValue)
- type ScriptParamValue = Value
- data BoostMode
- data ScoreMode
- data FunctionScoreFunction
- newtype Weight = Weight Float
- newtype Seed = Seed Float
- data FieldValueFactor = FieldValueFactor {}
- newtype Factor = Factor Float
- data FactorModifier
- newtype FactorMissingFieldValue = FactorMissingFieldValue Float
- functionScoreFunctionPair :: FunctionScoreFunction -> (Key, Value)
- parseFunctionScoreFunction :: Object -> Parser FunctionScoreFunction
- data WildcardQuery = WildcardQuery {}
- data FieldOrFields
- data SimpleQueryFlag
- data SimpleQueryStringQuery = SimpleQueryStringQuery {
- simpleQueryStringQuery :: QueryString
- simpleQueryStringField :: Maybe FieldOrFields
- simpleQueryStringOperator :: Maybe BooleanOperator
- simpleQueryStringAnalyzer :: Maybe Analyzer
- simpleQueryStringFlags :: Maybe (NonEmpty SimpleQueryFlag)
- simpleQueryStringLowercaseExpanded :: Maybe LowercaseExpanded
- simpleQueryStringLocale :: Maybe Locale
- newtype Regexp = Regexp Text
- data RegexpFlag
- data RegexpFlags
- data RegexpQuery = RegexpQuery {}
- newtype GreaterThan = GreaterThan Double
- newtype GreaterThanD = GreaterThanD UTCTime
- newtype GreaterThanEq = GreaterThanEq Double
- newtype GreaterThanEqD = GreaterThanEqD UTCTime
- newtype LessThan = LessThan Double
- newtype LessThanD = LessThanD UTCTime
- newtype LessThanEq = LessThanEq Double
- newtype LessThanEqD = LessThanEqD UTCTime
- data RangeQuery = RangeQuery {}
- 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
- mkRangeQuery :: FieldName -> RangeValue -> RangeQuery
- 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
- mkQueryStringQuery :: QueryString -> QueryStringQuery
- data PrefixQuery = PrefixQuery {}
- data MoreLikeThisFieldQuery = MoreLikeThisFieldQuery {
- moreLikeThisFieldText :: Text
- moreLikeThisFieldFields :: FieldName
- moreLikeThisFieldPercentMatch :: Maybe PercentMatch
- moreLikeThisFieldMinimumTermFreq :: Maybe MinimumTermFrequency
- moreLikeThisFieldMaxQueryTerms :: Maybe MaxQueryTerms
- moreLikeThisFieldStopWords :: Maybe (NonEmpty StopWord)
- moreLikeThisFieldMinDocFrequency :: Maybe MinDocFrequency
- moreLikeThisFieldMaxDocFrequency :: Maybe MaxDocFrequency
- moreLikeThisFieldMinWordLength :: Maybe MinWordLength
- moreLikeThisFieldMaxWordLength :: Maybe MaxWordLength
- moreLikeThisFieldBoostTerms :: Maybe BoostTerms
- moreLikeThisFieldBoost :: Maybe Boost
- moreLikeThisFieldAnalyzer :: Maybe Analyzer
- data MoreLikeThisQuery = MoreLikeThisQuery {
- moreLikeThisText :: Text
- moreLikeThisFields :: Maybe (NonEmpty FieldName)
- moreLikeThisPercentMatch :: Maybe PercentMatch
- moreLikeThisMinimumTermFreq :: Maybe MinimumTermFrequency
- moreLikeThisMaxQueryTerms :: Maybe MaxQueryTerms
- moreLikeThisStopWords :: Maybe (NonEmpty StopWord)
- moreLikeThisMinDocFrequency :: Maybe MinDocFrequency
- moreLikeThisMaxDocFrequency :: Maybe MaxDocFrequency
- moreLikeThisMinWordLength :: Maybe MinWordLength
- moreLikeThisMaxWordLength :: Maybe MaxWordLength
- moreLikeThisBoostTerms :: Maybe BoostTerms
- moreLikeThisBoost :: Maybe Boost
- moreLikeThisAnalyzer :: Maybe Analyzer
- 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
- matchQueryBoost :: Maybe Boost
- matchQueryMinimumShouldMatch :: Maybe Text
- matchQueryFuzziness :: Maybe Fuzziness
- data MatchQueryType
- 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 MultiMatchQueryType
- mkMatchQuery :: FieldName -> QueryString -> MatchQuery
- mkMultiMatchQuery :: [FieldName] -> QueryString -> MultiMatchQuery
- data FuzzyQuery = FuzzyQuery {}
- data FuzzyLikeFieldQuery = FuzzyLikeFieldQuery {}
- data FuzzyLikeThisQuery = FuzzyLikeThisQuery {}
- data BooleanOperator
- data Fuzziness
- data ZeroTermsQuery
- fieldTagged :: (Monad m, MonadFail m) => (FieldName -> Object -> m a) -> Object -> m a
- data CommonMinimumMatch
- 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 MinimumMatchHighLow = MinimumMatchHighLow {}
- module Data.Aeson.KeyMap
- data BoolMatch
- data BoolQuery = BoolQuery {}
- data BoostingQuery = BoostingQuery {}
- type Cache = Bool
- data ComponentFunctionScoreFunction = ComponentFunctionScoreFunction {}
- data DisMaxQuery = DisMaxQuery {}
- data Distance = Distance {}
- data DistanceRange = DistanceRange {}
- data DistanceType
- data DistanceUnit
- = Miles
- | Yards
- | Feet
- | Inches
- | Kilometers
- | Meters
- | Centimeters
- | Millimeters
- | NauticalMiles
- newtype Filter = Filter {}
- data FunctionScoreFunctions
- data FunctionScoreQuery = FunctionScoreQuery {}
- data GeoBoundingBox = GeoBoundingBox {
- topLeft :: LatLon
- bottomRight :: LatLon
- data GeoBoundingBoxConstraint = GeoBoundingBoxConstraint {}
- data GeoFilterType
- data GeoPoint = GeoPoint {}
- data HasChildQuery = HasChildQuery {}
- data HasParentQuery = HasParentQuery {}
- data IndicesQuery = IndicesQuery {}
- data InnerHits = InnerHits {}
- data LatLon = LatLon {}
- data NestedQuery = NestedQuery {}
- data OptimizeBbox
- data Query
- = TermQuery Term (Maybe Boost)
- | TermsQuery Key (NonEmpty Text)
- | QueryMatchQuery MatchQuery
- | QueryMultiMatchQuery MultiMatchQuery
- | QueryBoolQuery BoolQuery
- | QueryBoostingQuery BoostingQuery
- | QueryCommonTermsQuery CommonTermsQuery
- | ConstantScoreQuery Query Boost
- | QueryFunctionScoreQuery FunctionScoreQuery
- | QueryDisMaxQuery DisMaxQuery
- | QueryFuzzyLikeThisQuery FuzzyLikeThisQuery
- | QueryFuzzyLikeFieldQuery FuzzyLikeFieldQuery
- | QueryFuzzyQuery FuzzyQuery
- | QueryHasChildQuery HasChildQuery
- | QueryHasParentQuery HasParentQuery
- | IdsQuery [DocId]
- | QueryIndicesQuery IndicesQuery
- | MatchAllQuery (Maybe Boost)
- | QueryMoreLikeThisQuery MoreLikeThisQuery
- | QueryMoreLikeThisFieldQuery MoreLikeThisFieldQuery
- | QueryNestedQuery NestedQuery
- | QueryPrefixQuery PrefixQuery
- | QueryQueryStringQuery QueryStringQuery
- | QuerySimpleQueryStringQuery SimpleQueryStringQuery
- | QueryRangeQuery RangeQuery
- | QueryRegexpQuery RegexpQuery
- | QueryExistsQuery FieldName
- | QueryMatchNoneQuery
- | QueryWildcardQuery WildcardQuery
- data RangeExecution
- data ScoreType
- newtype TemplateQueryKeyValuePairs = TemplateQueryKeyValuePairs (KeyMap TemplateQueryValue)
- type TemplateQueryValue = Text
- data Term = Term {}
- defaultCache :: Cache
- functionScoreFunctionsPair :: FunctionScoreFunctions -> (Key, Value)
- mkBoolQuery :: [Query] -> [Filter] -> [Query] -> [Query] -> BoolQuery
- showDistanceUnit :: DistanceUnit -> Text
- data PointInTime = PointInTime {}
- pointInTimeIdLens :: Lens' PointInTime Text
- pointInTimeKeepAliveLens :: Lens' PointInTime Text
- data BoundTransportAddress = BoundTransportAddress {}
- newtype BuildHash = BuildHash {}
- data CPUInfo = CPUInfo {
- cpuCacheSize :: Bytes
- cpuCoresPerSocket :: Int
- cpuTotalSockets :: Int
- cpuTotalCores :: Int
- cpuMHZ :: Int
- cpuModel :: Text
- cpuVendor :: Text
- newtype ClusterName = ClusterName {
- clusterName :: Text
- newtype EsAddress = EsAddress {}
- newtype EsPassword = EsPassword {
- esPassword :: Text
- newtype EsUsername = EsUsername {
- esUsername :: Text
- newtype FullNodeId = FullNodeId {
- fullNodeId :: Text
- data InitialShardCount
- data JVMBufferPoolStats = JVMBufferPoolStats {}
- newtype JVMGCCollector = JVMGCCollector {}
- data JVMGCStats = JVMGCStats {}
- data JVMMemoryInfo = JVMMemoryInfo {}
- newtype JVMMemoryPool = JVMMemoryPool {}
- data JVMPoolStats = JVMPoolStats {}
- newtype JVMVersion = JVMVersion {
- unJVMVersion :: Text
- data LoadAvgs = LoadAvgs {}
- newtype MacAddress = MacAddress {
- macAddress :: Text
- newtype NetworkInterfaceName = NetworkInterfaceName {}
- data NodeAttrFilter = NodeAttrFilter {}
- newtype NodeAttrName = NodeAttrName Text
- data NodeBreakerStats = NodeBreakerStats {}
- data NodeBreakersStats = NodeBreakersStats {}
- data NodeDataPathStats = NodeDataPathStats {
- nodeDataPathDiskServiceTime :: Maybe Double
- nodeDataPathDiskQueue :: Maybe Double
- nodeDataPathIOSize :: Maybe Bytes
- nodeDataPathWriteSize :: Maybe Bytes
- nodeDataPathReadSize :: Maybe Bytes
- nodeDataPathIOOps :: Maybe Int
- nodeDataPathWrites :: Maybe Int
- nodeDataPathReads :: Maybe Int
- nodeDataPathAvailable :: Bytes
- nodeDataPathFree :: Bytes
- nodeDataPathTotal :: Bytes
- nodeDataPathType :: Maybe Text
- nodeDataPathDevice :: Maybe Text
- nodeDataPathMount :: Text
- nodeDataPathPath :: Text
- data NodeFSStats = NodeFSStats {}
- data NodeFSTotalStats = NodeFSTotalStats {
- nodeFSTotalDiskServiceTime :: Maybe Double
- nodeFSTotalDiskQueue :: Maybe Double
- nodeFSTotalIOSize :: Maybe Bytes
- nodeFSTotalWriteSize :: Maybe Bytes
- nodeFSTotalReadSize :: Maybe Bytes
- nodeFSTotalIOOps :: Maybe Int
- nodeFSTotalWrites :: Maybe Int
- nodeFSTotalReads :: Maybe Int
- nodeFSTotalAvailable :: Bytes
- nodeFSTotalFree :: Bytes
- nodeFSTotalTotal :: Bytes
- data NodeHTTPInfo = NodeHTTPInfo {}
- data NodeHTTPStats = NodeHTTPStats {}
- data NodeIndicesStats = NodeIndicesStats {
- nodeIndicesStatsRecoveryThrottleTime :: Maybe NominalDiffTime
- nodeIndicesStatsRecoveryCurrentAsTarget :: Maybe Int
- nodeIndicesStatsRecoveryCurrentAsSource :: Maybe Int
- nodeIndicesStatsQueryCacheMisses :: Maybe Int
- nodeIndicesStatsQueryCacheHits :: Maybe Int
- nodeIndicesStatsQueryCacheEvictions :: Maybe Int
- nodeIndicesStatsQueryCacheSize :: Maybe Bytes
- nodeIndicesStatsSuggestCurrent :: Maybe Int
- nodeIndicesStatsSuggestTime :: Maybe NominalDiffTime
- nodeIndicesStatsSuggestTotal :: Maybe Int
- nodeIndicesStatsTranslogSize :: Bytes
- nodeIndicesStatsTranslogOps :: Int
- nodeIndicesStatsSegFixedBitSetMemory :: Maybe Bytes
- nodeIndicesStatsSegVersionMapMemory :: Bytes
- nodeIndicesStatsSegIndexWriterMaxMemory :: Maybe Bytes
- nodeIndicesStatsSegIndexWriterMemory :: Bytes
- nodeIndicesStatsSegMemory :: Bytes
- nodeIndicesStatsSegCount :: Int
- nodeIndicesStatsCompletionSize :: Bytes
- nodeIndicesStatsPercolateQueries :: Maybe Int
- nodeIndicesStatsPercolateMemory :: Maybe Bytes
- nodeIndicesStatsPercolateCurrent :: Maybe Int
- nodeIndicesStatsPercolateTime :: Maybe NominalDiffTime
- nodeIndicesStatsPercolateTotal :: Maybe Int
- nodeIndicesStatsFieldDataEvictions :: Int
- nodeIndicesStatsFieldDataMemory :: Bytes
- nodeIndicesStatsWarmerTotalTime :: NominalDiffTime
- nodeIndicesStatsWarmerTotal :: Int
- nodeIndicesStatsWarmerCurrent :: Int
- nodeIndicesStatsFlushTotalTime :: NominalDiffTime
- nodeIndicesStatsFlushTotal :: Int
- nodeIndicesStatsRefreshTotalTime :: NominalDiffTime
- nodeIndicesStatsRefreshTotal :: Int
- nodeIndicesStatsMergesTotalSize :: Bytes
- nodeIndicesStatsMergesTotalDocs :: Int
- nodeIndicesStatsMergesTotalTime :: NominalDiffTime
- nodeIndicesStatsMergesTotal :: Int
- nodeIndicesStatsMergesCurrentSize :: Bytes
- nodeIndicesStatsMergesCurrentDocs :: Int
- nodeIndicesStatsMergesCurrent :: Int
- nodeIndicesStatsSearchFetchCurrent :: Int
- nodeIndicesStatsSearchFetchTime :: NominalDiffTime
- nodeIndicesStatsSearchFetchTotal :: Int
- nodeIndicesStatsSearchQueryCurrent :: Int
- nodeIndicesStatsSearchQueryTime :: NominalDiffTime
- nodeIndicesStatsSearchQueryTotal :: Int
- nodeIndicesStatsSearchOpenContexts :: Int
- nodeIndicesStatsGetCurrent :: Int
- nodeIndicesStatsGetMissingTime :: NominalDiffTime
- nodeIndicesStatsGetMissingTotal :: Int
- nodeIndicesStatsGetExistsTime :: NominalDiffTime
- nodeIndicesStatsGetExistsTotal :: Int
- nodeIndicesStatsGetTime :: NominalDiffTime
- nodeIndicesStatsGetTotal :: Int
- nodeIndicesStatsIndexingThrottleTime :: Maybe NominalDiffTime
- nodeIndicesStatsIndexingIsThrottled :: Maybe Bool
- nodeIndicesStatsIndexingNoopUpdateTotal :: Maybe Int
- nodeIndicesStatsIndexingDeleteCurrent :: Int
- nodeIndicesStatsIndexingDeleteTime :: NominalDiffTime
- nodeIndicesStatsIndexingDeleteTotal :: Int
- nodeIndicesStatsIndexingIndexCurrent :: Int
- nodeIndicesStatsIndexingIndexTime :: NominalDiffTime
- nodeIndicesStatsIndexingTotal :: Int
- nodeIndicesStatsStoreThrottleTime :: Maybe NominalDiffTime
- nodeIndicesStatsStoreSize :: Bytes
- nodeIndicesStatsDocsDeleted :: Int
- nodeIndicesStatsDocsCount :: Int
- data NodeInfo = NodeInfo {
- nodeInfoHTTPAddress :: Maybe EsAddress
- nodeInfoBuild :: BuildHash
- nodeInfoESVersion :: VersionNumber
- nodeInfoIP :: Server
- nodeInfoHost :: Server
- nodeInfoTransportAddress :: EsAddress
- nodeInfoName :: NodeName
- nodeInfoFullId :: FullNodeId
- nodeInfoPlugins :: [NodePluginInfo]
- nodeInfoHTTP :: NodeHTTPInfo
- nodeInfoTransport :: NodeTransportInfo
- nodeInfoNetwork :: Maybe NodeNetworkInfo
- nodeInfoThreadPool :: Map Text NodeThreadPoolInfo
- nodeInfoJVM :: NodeJVMInfo
- nodeInfoProcess :: NodeProcessInfo
- nodeInfoOS :: NodeOSInfo
- nodeInfoSettings :: Object
- data NodeJVMInfo = NodeJVMInfo {}
- data NodeJVMStats = NodeJVMStats {
- nodeJVMStatsMappedBufferPool :: JVMBufferPoolStats
- nodeJVMStatsDirectBufferPool :: JVMBufferPoolStats
- nodeJVMStatsGCOldCollector :: JVMGCStats
- nodeJVMStatsGCYoungCollector :: JVMGCStats
- nodeJVMStatsPeakThreadsCount :: Int
- nodeJVMStatsThreadsCount :: Int
- nodeJVMStatsOldPool :: JVMPoolStats
- nodeJVMStatsSurvivorPool :: JVMPoolStats
- nodeJVMStatsYoungPool :: JVMPoolStats
- nodeJVMStatsNonHeapCommitted :: Bytes
- nodeJVMStatsNonHeapUsed :: Bytes
- nodeJVMStatsHeapMax :: Bytes
- nodeJVMStatsHeapCommitted :: Bytes
- nodeJVMStatsHeapUsedPercent :: Int
- nodeJVMStatsHeapUsed :: Bytes
- nodeJVMStatsUptime :: NominalDiffTime
- nodeJVMStatsTimestamp :: UTCTime
- newtype NodeName = NodeName {}
- data NodeNetworkInfo = NodeNetworkInfo {}
- data NodeNetworkInterface = NodeNetworkInterface {}
- data NodeNetworkStats = NodeNetworkStats {}
- data NodeOSInfo = NodeOSInfo {}
- data NodeOSStats = NodeOSStats {}
- data NodePluginInfo = NodePluginInfo {}
- data NodeProcessInfo = NodeProcessInfo {}
- data NodeProcessStats = NodeProcessStats {}
- data NodeSelection
- data NodeSelector
- data NodeStats = NodeStats {
- nodeStatsName :: NodeName
- nodeStatsFullId :: FullNodeId
- nodeStatsBreakersStats :: Maybe NodeBreakersStats
- nodeStatsHTTP :: NodeHTTPStats
- nodeStatsTransport :: NodeTransportStats
- nodeStatsFS :: NodeFSStats
- nodeStatsNetwork :: Maybe NodeNetworkStats
- nodeStatsThreadPool :: Map Text NodeThreadPoolStats
- nodeStatsJVM :: NodeJVMStats
- nodeStatsProcess :: NodeProcessStats
- nodeStatsOS :: NodeOSStats
- nodeStatsIndices :: NodeIndicesStats
- data NodeThreadPoolInfo = NodeThreadPoolInfo {}
- data NodeThreadPoolStats = NodeThreadPoolStats {}
- data NodeTransportInfo = NodeTransportInfo {}
- data NodeTransportStats = NodeTransportStats {}
- data NodesInfo = NodesInfo {}
- data NodesStats = NodesStats {}
- newtype PID = PID {}
- newtype PluginName = PluginName {
- pluginName :: Text
- data ShardResult = ShardResult {
- shardTotal :: Int
- shardsSuccessful :: Int
- shardsSkipped :: Int
- shardsFailed :: Int
- newtype ShardsResult = ShardsResult {}
- data ThreadPool = ThreadPool {}
- data ThreadPoolSize
- data ThreadPoolType
- data Version = Version {}
- newtype VersionNumber = VersionNumber {}
- nodeOSRefreshIntervalLens :: Lens' NodeOSInfo NominalDiffTime
- nodeOSNameLens :: Lens' NodeOSInfo Text
- nodeOSArchLens :: Lens' NodeOSInfo Text
- nodeOSVersionLens :: Lens' NodeOSInfo Text
- nodeOSAvailableProcessorsLens :: Lens' NodeOSInfo Int
- nodeOSAllocatedProcessorsLens :: Lens' NodeOSInfo Int
- cpuCacheSizeLens :: Lens' CPUInfo Bytes
- cpuCoresPerSocketLens :: Lens' CPUInfo Int
- cpuTotalSocketsLens :: Lens' CPUInfo Int
- cpuTotalCoresLens :: Lens' CPUInfo Int
- cpuMHZLens :: Lens' CPUInfo Int
- cpuModelLens :: Lens' CPUInfo Text
- cpuVendorLens :: Lens' CPUInfo Text
- nodeProcessMLockAllLens :: Lens' NodeProcessInfo Bool
- nodeProcessMaxFileDescriptorsLens :: Lens' NodeProcessInfo (Maybe Int)
- nodeProcessIdLens :: Lens' NodeProcessInfo PID
- nodeProcessRefreshIntervalLens :: Lens' NodeProcessInfo NominalDiffTime
- srShardsLens :: Lens' ShardsResult ShardResult
- shardTotalLens :: Lens' ShardResult Int
- shardsSuccessfulLens :: Lens' ShardResult Int
- shardsSkippedLens :: Lens' ShardResult Int
- shardsFailedLens :: Lens' ShardResult Int
- versionNumberLens :: Lens' Version VersionNumber
- versionBuildHashLens :: Lens' Version BuildHash
- versionBuildDateLens :: Lens' Version UTCTime
- versionBuildSnapshotLens :: Lens' Version Bool
- versionLuceneVersionLens :: Lens' Version VersionNumber
- newtype From = From Int
- newtype Size = Size Int
- newtype HitFields = HitFields (Map Text [Value])
- type Score = Maybe Double
- newtype ShardId = ShardId {}
- newtype DocId = DocId Text
- newtype FieldName = FieldName Text
- newtype RelationName = RelationName Text
- newtype QueryString = QueryString Text
- newtype CacheName = CacheName Text
- newtype CacheKey = CacheKey Text
- newtype Existence = Existence Bool
- newtype NullValue = NullValue Bool
- newtype CutoffFrequency = CutoffFrequency Double
- newtype Analyzer = Analyzer Text
- newtype MaxExpansions = MaxExpansions Int
- newtype Lenient = Lenient Bool
- newtype Tiebreaker = Tiebreaker Double
- newtype MinimumMatch = MinimumMatch Int
- newtype DisableCoord = DisableCoord Bool
- newtype IgnoreTermFrequency = IgnoreTermFrequency Bool
- newtype MinimumTermFrequency = MinimumTermFrequency Int
- newtype MaxQueryTerms = MaxQueryTerms Int
- newtype PrefixLength = PrefixLength Int
- newtype PercentMatch = PercentMatch Double
- newtype StopWord = StopWord Text
- newtype QueryPath = QueryPath Text
- newtype AllowLeadingWildcard = AllowLeadingWildcard Bool
- newtype LowercaseExpanded = LowercaseExpanded Bool
- newtype EnablePositionIncrements = EnablePositionIncrements Bool
- newtype AnalyzeWildcard = AnalyzeWildcard Bool
- newtype GeneratePhraseQueries = GeneratePhraseQueries Bool
- newtype Locale = Locale Text
- newtype MaxWordLength = MaxWordLength Int
- newtype MinWordLength = MinWordLength Int
- newtype PhraseSlop = PhraseSlop Int
- newtype MinDocFrequency = MinDocFrequency Int
- newtype MaxDocFrequency = MaxDocFrequency Int
- newtype AggregateParentScore = AggregateParentScore Bool
- newtype IgnoreUnmapped = IgnoreUnmapped Bool
- newtype MinChildren = MinChildren Int
- newtype MaxChildren = MaxChildren Int
- newtype POSIXMS = POSIXMS {}
- newtype Boost = Boost Double
- newtype BoostTerms = BoostTerms Double
- newtype ReplicaCount = ReplicaCount Int
- newtype ShardCount = ShardCount Int
- data IndexName
- unIndexName :: IndexName -> Text
- mkIndexName :: Text -> Either Text IndexName
- qqIndexName :: QuasiQuoter
- newtype IndexAliasName = IndexAliasName {}
- newtype MaybeNA a = MaybeNA {}
- newtype SnapshotName = SnapshotName {
- snapshotName :: Text
- newtype MS = MS NominalDiffTime
- unMS :: MS -> NominalDiffTime
- newtype TokenFilter = TokenFilter Text
- newtype CharFilter = CharFilter Text
- data AliasRouting
- data AllocationPolicy
- data CompoundFormat
- data Compression
- data FSType
- newtype FieldDefinition = FieldDefinition {}
- data FieldType
- data ForceMergeIndexSettings = ForceMergeIndexSettings {}
- data IndexAlias = IndexAlias {}
- data IndexAliasAction
- data IndexAliasCreate = IndexAliasCreate {}
- newtype IndexAliasRouting = IndexAliasRouting RoutingValue
- data IndexAliasSummary = IndexAliasSummary {}
- newtype IndexAliasesSummary = IndexAliasesSummary {}
- data IndexDocumentSettings = IndexDocumentSettings {}
- data IndexMappingsLimits = IndexMappingsLimits {}
- newtype IndexPattern = IndexPattern Text
- data IndexSelection
- data IndexSettings = IndexSettings {}
- data IndexSettingsSummary = IndexSettingsSummary {}
- data IndexTemplate = IndexTemplate {}
- data JoinRelation
- newtype Mapping = Mapping {}
- data MappingField = MappingField {}
- newtype NominalDiffTimeJSON = NominalDiffTimeJSON {}
- data OpenCloseIndex
- data ReplicaBounds
- newtype RoutingValue = RoutingValue {
- routingValue :: Text
- newtype SearchAliasRouting = SearchAliasRouting (NonEmpty RoutingValue)
- data Status = Status {
- name :: Text
- cluster_name :: Text
- cluster_uuid :: Text
- version :: Version
- tagline :: Text
- newtype TemplateName = TemplateName Text
- data UpdatableIndexSetting
- = NumberOfReplicas ReplicaCount
- | AutoExpandReplicas ReplicaBounds
- | BlocksReadOnly Bool
- | BlocksRead Bool
- | BlocksWrite Bool
- | BlocksMetaData Bool
- | RefreshInterval NominalDiffTime
- | IndexConcurrency Int
- | FailOnMergeFailure Bool
- | TranslogFlushThresholdOps Int
- | TranslogFlushThresholdSize Bytes
- | TranslogFlushThresholdPeriod NominalDiffTime
- | TranslogDisableFlush Bool
- | CacheFilterMaxSize (Maybe Bytes)
- | CacheFilterExpire (Maybe NominalDiffTime)
- | GatewaySnapshotInterval NominalDiffTime
- | RoutingAllocationInclude (NonEmpty NodeAttrFilter)
- | RoutingAllocationExclude (NonEmpty NodeAttrFilter)
- | RoutingAllocationRequire (NonEmpty NodeAttrFilter)
- | RoutingAllocationEnable AllocationPolicy
- | RoutingAllocationShardsPerNode ShardCount
- | RecoveryInitialShards InitialShardCount
- | GCDeletes NominalDiffTime
- | TTLDisablePurge Bool
- | TranslogFSType FSType
- | CompressionSetting Compression
- | IndexCompoundFormat CompoundFormat
- | IndexCompoundOnFlush Bool
- | WarmerEnabled Bool
- | MappingTotalFieldsLimit Int
- | AnalysisSetting Analysis
- | UnassignedNodeLeftDelayedTimeout NominalDiffTime
- defaultForceMergeIndexSettings :: ForceMergeIndexSettings
- defaultIndexDocumentSettings :: IndexDocumentSettings
- defaultIndexMappingsLimits :: IndexMappingsLimits
- defaultIndexSettings :: IndexSettings
- nameLens :: Lens' Status Text
- clusterNameLens :: Lens' Status Text
- clusterUuidLens :: Lens' Status Text
- versionLens :: Lens' Status Version
- taglineLens :: Lens' Status Text
- indexShardsLens :: Lens' IndexSettings ShardCount
- indexReplicasLens :: Lens' IndexSettings ReplicaCount
- indexMappingsLimitsLens :: Lens' IndexSettings IndexMappingsLimits
- indexMappingsLimitDepthLens :: Lens' IndexMappingsLimits (Maybe Int)
- indexMappingsLimitNestedFieldsLens :: Lens' IndexMappingsLimits (Maybe Int)
- indexMappingsLimitNestedObjectsLens :: Lens' IndexMappingsLimits (Maybe Int)
- indexMappingsLimitFieldNameLengthLens :: Lens' IndexMappingsLimits (Maybe Int)
- maxNumSegmentsLens :: Lens' ForceMergeIndexSettings (Maybe Int)
- onlyExpungeDeletesLens :: Lens' ForceMergeIndexSettings Bool
- flushAfterOptimizeLens :: Lens' ForceMergeIndexSettings Bool
- sSummaryIndexNameLens :: Lens' IndexSettingsSummary IndexName
- sSummaryFixedSettingsLens :: Lens' IndexSettingsSummary IndexSettings
- sSummaryUpdateableLens :: Lens' IndexSettingsSummary [UpdatableIndexSetting]
- fieldTypeLens :: Lens' FieldDefinition FieldType
- templatePatternsLens :: Lens' IndexTemplate [IndexPattern]
- templateSettingsLens :: Lens' IndexTemplate (Maybe IndexSettings)
- templateMappingsLens :: Lens' IndexTemplate Value
- mappingFieldNameLens :: Lens' MappingField FieldName
- fieldDefinitionLens :: Lens' MappingField FieldDefinition
- mappingFieldsLens :: Lens' Mapping [MappingField]
- srcIndexLens :: Lens' IndexAlias IndexName
- indexAliasLens :: Lens' IndexAlias IndexAliasName
- aliasCreateRoutingLens :: Lens' IndexAliasCreate (Maybe AliasRouting)
- aliasCreateFilterLens :: Lens' IndexAliasCreate (Maybe Filter)
- routingValueLens :: Lens' RoutingValue Text
- indexAliasesSummaryLens :: Lens' IndexAliasesSummary [IndexAliasSummary]
- indexAliasSummaryAliasLens :: Lens' IndexAliasSummary IndexAlias
- indexAliasSummaryCreateLens :: Lens' IndexAliasSummary IndexAliasCreate
- idsVersionControlLens :: Lens' IndexDocumentSettings VersionControl
- idsJoinRelationLens :: Lens' IndexDocumentSettings (Maybe JoinRelation)
- type HitHighlight = Map Text [Text]
- 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])
- highlightSettingsPairs :: Maybe HighlightSettings -> [Pair]
- plainHighPairs :: Maybe PlainHighlight -> [Pair]
- postHighPairs :: Maybe PostingsHighlight -> [Pair]
- fastVectorHighPairs :: Maybe FastVectorHighlight -> [Pair]
- commonHighlightPairs :: Maybe CommonHighlight -> [Pair]
- nonPostingsToPairs :: Maybe NonPostings -> [Pair]
- highlightTagToPairs :: Maybe HighlightTag -> [Pair]
- newtype CountQuery = CountQuery {
- countQuery :: Query
- data CountResponse = CountResponse {}
- data CountShards = CountShards {}
- crCountLens :: Lens' CountResponse Natural
- crShardsLens :: Lens' CountResponse CountShards
- csTotalLens :: Lens' CountShards Int
- csSuccessfulLens :: Lens' CountShards Int
- csFailedLens :: Lens' CountShards Int
- data BulkOperation
- = BulkIndex IndexName DocId Value
- | BulkIndexAuto IndexName Value
- | BulkIndexEncodingAuto IndexName Encoding
- | BulkCreate IndexName DocId Value
- | BulkCreateEncoding IndexName DocId Encoding
- | BulkDelete IndexName DocId
- | BulkUpdate IndexName DocId Value
- | BulkUpsert IndexName DocId UpsertPayload [UpsertActionMetadata]
- data UpsertActionMetadata
- data UpsertPayload
- buildUpsertActionMetadata :: UpsertActionMetadata -> Pair
- data BulkResponse = BulkResponse {
- bulkTook :: Int
- bulkErrors :: Bool
- bulkActionItems :: [BulkActionItem]
- data BulkActionItem = BulkActionItem {}
- data BulkItem = BulkItem {}
- data BulkAction
- data BulkError = BulkError {}
- bulkTookLens :: Lens' BulkResponse Int
- bulkErrorsLens :: Lens' BulkResponse Bool
- bulkActionItemsLens :: Lens' BulkResponse [BulkActionItem]
- baiActionLens :: Lens' BulkActionItem BulkAction
- baiItemLens :: Lens' BulkActionItem BulkItem
- biIndexLens :: Lens' BulkItem Text
- biIdLens :: Lens' BulkItem Text
- biStatusLens :: Lens' BulkItem (Maybe Int)
- biErrorLens :: Lens' BulkItem (Maybe BulkError)
- beTypeLens :: Lens' BulkError Text
- beReasonLens :: Lens' BulkError Text
- data Analysis = Analysis {}
- analysisAnalyzerLens :: Lens' Analysis (Map Text AnalyzerDefinition)
- analysisTokenizerLens :: Lens' Analysis (Map Text TokenizerDefinition)
- analysisTokenFilterLens :: Lens' Analysis (Map Text TokenFilterDefinition)
- analysisCharFilterLens :: Lens' Analysis (Map Text CharFilterDefinition)
- newtype Tokenizer = Tokenizer Text
- data AnalyzerDefinition = AnalyzerDefinition {}
- analyzerDefinitionTokenizerLens :: Lens' AnalyzerDefinition (Maybe Tokenizer)
- analyzerDefinitionFilterLens :: Lens' AnalyzerDefinition [TokenFilter]
- analyzerDefinitionCharFilterLens :: Lens' AnalyzerDefinition [CharFilter]
- data CharFilterDefinition
- data TokenizerDefinition
- data Ngram = Ngram {
- ngramMinGram :: Int
- ngramMaxGram :: Int
- ngramTokenChars :: [TokenChar]
- data TokenChar
- data TokenFilterDefinition
- = TokenFilterDefinitionLowercase (Maybe Language)
- | TokenFilterDefinitionUppercase (Maybe Language)
- | TokenFilterDefinitionApostrophe
- | TokenFilterDefinitionReverse
- | TokenFilterDefinitionSnowball Language
- | TokenFilterDefinitionShingle Shingle
- | TokenFilterDefinitionStemmer Language
- | TokenFilterDefinitionStop (Either Language [StopWord])
- | TokenFilterDefinitionEdgeNgram NgramFilter (Maybe EdgeNgramFilterSide)
- | TokenFilterDefinitionNgram NgramFilter
- | TokenFilterTruncate Int
- data NgramFilter = NgramFilter {}
- ngramFilterToPairs :: NgramFilter -> [Pair]
- ngramFilterFromJSONObject :: Object -> Parser NgramFilter
- data EdgeNgramFilterSide
- data Language
- = Arabic
- | Armenian
- | Basque
- | Bengali
- | Brazilian
- | Bulgarian
- | Catalan
- | Cjk
- | Czech
- | Danish
- | Dutch
- | English
- | Finnish
- | French
- | Galician
- | German
- | German2
- | Greek
- | Hindi
- | Hungarian
- | Indonesian
- | Irish
- | Italian
- | Kp
- | Latvian
- | Lithuanian
- | Lovins
- | Norwegian
- | Persian
- | Porter
- | Portuguese
- | Romanian
- | Russian
- | Sorani
- | Spanish
- | Swedish
- | Thai
- | Turkish
- languageToText :: Language -> Text
- languageFromText :: Text -> Maybe Language
- data Shingle = Shingle {}
- shingleMaxSizeLens :: Lens' Shingle Int
- shingleMinSizeLens :: Lens' Shingle Int
- shingleOutputUnigramsLens :: Lens' Shingle Bool
- shingleOutputUnigramsIfNoShinglesLens :: Lens' Shingle Bool
- shingleTokenSeparatorLens :: Lens' Shingle Text
- shingleFillerTokenLens :: Lens' Shingle Text
- type Aggregations = Map Key Aggregation
- emptyAggregations :: Aggregations
- mkAggregations :: Key -> Aggregation -> Aggregations
- data Aggregation
- = TermsAgg TermsAggregation
- | CardinalityAgg CardinalityAggregation
- | DateHistogramAgg DateHistogramAggregation
- | ValueCountAgg ValueCountAggregation
- | FilterAgg FilterAggregation
- | DateRangeAgg DateRangeAggregation
- | MissingAgg MissingAggregation
- | TopHitsAgg TopHitsAggregation
- | StatsAgg StatisticsAggregation
- | SumAgg SumAggregation
- data TopHitsAggregation = TopHitsAggregation {}
- taFromLens :: Lens' TopHitsAggregation (Maybe From)
- taSizeLens :: Lens' TopHitsAggregation (Maybe Size)
- taSortLens :: Lens' TopHitsAggregation (Maybe Sort)
- data MissingAggregation = MissingAggregation {}
- maFieldLens :: Lens' MissingAggregation Text
- 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
- termLens :: Lens' TermsAggregation (Either Text Text)
- termIncludeLens :: Lens' TermsAggregation (Maybe TermInclusion)
- termExcludeLens :: Lens' TermsAggregation (Maybe TermInclusion)
- termOrderLens :: Lens' TermsAggregation (Maybe TermOrder)
- termMinDocCountLens :: Lens' TermsAggregation (Maybe Int)
- termSizeLens :: Lens' TermsAggregation (Maybe Int)
- termShardSizeLens :: Lens' TermsAggregation (Maybe Int)
- termCollectModeLens :: Lens' TermsAggregation (Maybe CollectionMode)
- termExecutionHintLens :: Lens' TermsAggregation (Maybe ExecutionHint)
- termAggsLens :: Lens' TermsAggregation (Maybe Aggregations)
- data CardinalityAggregation = CardinalityAggregation {}
- cardinalityFieldLens :: Lens' CardinalityAggregation FieldName
- precisionThresholdLens :: Lens' CardinalityAggregation (Maybe Int)
- data DateHistogramAggregation = DateHistogramAggregation {}
- dateFieldLens :: Lens' DateHistogramAggregation FieldName
- dateIntervalLens :: Lens' DateHistogramAggregation Interval
- dateFormatLens :: Lens' DateHistogramAggregation (Maybe Text)
- datePreZoneLens :: Lens' DateHistogramAggregation (Maybe Text)
- datePostZoneLens :: Lens' DateHistogramAggregation (Maybe Text)
- datePreOffsetLens :: Lens' DateHistogramAggregation (Maybe Text)
- datePostOffsetLens :: Lens' DateHistogramAggregation (Maybe Text)
- dateAggsLens :: Lens' DateHistogramAggregation (Maybe Aggregations)
- data DateRangeAggregation = DateRangeAggregation {}
- draFieldLens :: Lens' DateRangeAggregation FieldName
- draFormatLens :: Lens' DateRangeAggregation (Maybe Text)
- draRangesLens :: Lens' DateRangeAggregation (NonEmpty DateRangeAggRange)
- data DateRangeAggRange
- data ValueCountAggregation
- data FilterAggregation = FilterAggregation {}
- faFilterLens :: Lens' FilterAggregation Filter
- faAggsLens :: Lens' FilterAggregation (Maybe Aggregations)
- data StatisticsAggregation = StatisticsAggregation {}
- statsTypeLens :: Lens' StatisticsAggregation StatsType
- statsFieldLens :: Lens' StatisticsAggregation FieldName
- data StatsType
- newtype SumAggregation = SumAggregation {}
- mkTermsAggregation :: Text -> TermsAggregation
- mkTermsScriptAggregation :: Text -> TermsAggregation
- mkDateHistogram :: FieldName -> Interval -> DateHistogramAggregation
- mkCardinalityAggregation :: FieldName -> CardinalityAggregation
- mkStatsAggregation :: FieldName -> StatisticsAggregation
- mkExtendedStatsAggregation :: FieldName -> StatisticsAggregation
- type AggregationResults = Map Key Value
- class BucketAggregation a where
- key :: a -> BucketValue
- docCount :: a -> Int
- aggs :: a -> Maybe AggregationResults
- data Bucket a = Bucket {
- buckets :: [a]
- bucketsLens :: Lens' (Bucket a) [a]
- data BucketValue
- data TermInclusion
- data TermOrder = TermOrder {}
- termSortFieldLens :: Lens' TermOrder Text
- termSortOrderLens :: Lens' TermOrder SortOrder
- data CollectionMode
- data ExecutionHint
- data DateMathExpr = DateMathExpr DateMathAnchor [DateMathModifier]
- data DateMathAnchor
- data DateMathModifier
- data DateMathUnit
- data TermsResult = TermsResult {}
- termKeyLens :: Lens' TermsResult BucketValue
- termsDocCountLens :: Lens' TermsResult Int
- termsAggsLens :: Lens' TermsResult (Maybe AggregationResults)
- data DateHistogramResult = DateHistogramResult {}
- dateKeyLens :: Lens' DateHistogramResult Int
- dateKeyStrLens :: Lens' DateHistogramResult (Maybe Text)
- dateDocCountLens :: Lens' DateHistogramResult Int
- dateHistogramAggsLens :: Lens' DateHistogramResult (Maybe AggregationResults)
- data DateRangeResult = DateRangeResult {}
- dateRangeKeyLens :: Lens' DateRangeResult Text
- dateRangeFromLens :: Lens' DateRangeResult (Maybe UTCTime)
- dateRangeFromAsStringLens :: Lens' DateRangeResult (Maybe Text)
- dateRangeToLens :: Lens' DateRangeResult (Maybe UTCTime)
- dateRangeToAsStringLens :: Lens' DateRangeResult (Maybe Text)
- dateRangeDocCountLens :: Lens' DateRangeResult Int
- dateRangeAggsLens :: Lens' DateRangeResult (Maybe AggregationResults)
- toTerms :: Key -> AggregationResults -> Maybe (Bucket TermsResult)
- toDateHistogram :: Key -> AggregationResults -> Maybe (Bucket DateHistogramResult)
- toMissing :: Key -> AggregationResults -> Maybe MissingResult
- toTopHits :: FromJSON a => Key -> AggregationResults -> Maybe (TopHitResult a)
- toAggResult :: FromJSON a => Key -> AggregationResults -> Maybe a
- getNamedSubAgg :: Object -> [Key] -> Maybe AggregationResults
- data MissingResult = MissingResult {}
- data TopHitResult a = TopHitResult {
- tarHits :: SearchHits a
- data HitsTotalRelation
- data HitsTotal = HitsTotal {}
- hitsTotalValueLens :: Lens' HitsTotal Int
- hitsTotalRelationLens :: Lens' HitsTotal HitsTotalRelation
- data SearchHits a = SearchHits {}
- searchHitsHitsTotalLens :: Lens' (SearchHits a) HitsTotal
- searchHitsMaxScoreLens :: Lens' (SearchHits a) Score
- searchHitsHitsLens :: Lens' (SearchHits a) [Hit a]
- type SearchAfterKey = [Value]
- data Hit a = Hit {
- hitIndex :: IndexName
- hitDocId :: DocId
- hitScore :: Score
- hitSource :: Maybe a
- hitSort :: Maybe SearchAfterKey
- hitFields :: Maybe HitFields
- hitHighlight :: Maybe HitHighlight
- hitInnerHits :: Maybe (KeyMap (TopHitResult Value))
- hitIndexLens :: Lens' (Hit a) IndexName
- hitDocIdLens :: Lens' (Hit a) DocId
- hitScoreLens :: Lens' (Hit a) Score
- hitSourceLens :: Lens' (Hit a) (Maybe a)
- hitSortLens :: Lens' (Hit a) (Maybe SearchAfterKey)
- hitFieldsLens :: Lens' (Hit a) (Maybe HitFields)
- hitHighlightLens :: Lens' (Hit a) (Maybe HitHighlight)
- hitInnerHitsLens :: Lens' (Hit a) (Maybe (KeyMap (TopHitResult Value)))
- newtype DocVersion = DocVersion {}
- newtype ExternalDocVersion = ExternalDocVersion DocVersion
- mkDocVersion :: Int -> Maybe DocVersion
- data VersionControl
- data BHRequest parsingContext responseBody = BHRequest {
- bhRequestMethod :: Method
- bhRequestEndpoint :: Endpoint
- bhRequestBody :: Maybe ByteString
- bhRequestParser :: BHResponse parsingContext responseBody -> Either EsProtocolException (ParsedEsResponse responseBody)
- data StatusIndependant
- data StatusDependant
- mkFullRequest :: (ParseBHResponse parsingContext, FromJSON responseBody) => Method -> Endpoint -> ByteString -> BHRequest parsingContext responseBody
- mkSimpleRequest :: (ParseBHResponse parsingContext, FromJSON responseBody) => Method -> Endpoint -> BHRequest parsingContext responseBody
- type ParsedEsResponse a = Either EsError a
- class ParseBHResponse parsingContext where
- parseBHResponse :: FromJSON a => BHResponse parsingContext a -> Either EsProtocolException (ParsedEsResponse a)
- newtype Server = Server Text
- data Endpoint = Endpoint {
- getRawEndpoint :: [Text]
- getRawEndpointQueries :: [(Text, Maybe Text)]
- mkEndpoint :: [Text] -> Endpoint
- withQueries :: Endpoint -> [(Text, Maybe Text)] -> Endpoint
- getEndpoint :: Server -> Endpoint -> Text
- withBHResponse :: forall a parsingContext b. (Either EsProtocolException (ParsedEsResponse a) -> BHResponse StatusDependant a -> b) -> BHRequest parsingContext a -> BHRequest StatusDependant b
- withBHResponse_ :: forall a parsingContext b. (BHResponse StatusDependant a -> b) -> BHRequest parsingContext a -> BHRequest StatusDependant b
- withBHResponseParsedEsResponse :: forall a parsingContext. BHRequest parsingContext a -> BHRequest StatusDependant (ParsedEsResponse a)
- keepBHResponse :: forall a parsingContext. BHRequest parsingContext a -> BHRequest StatusDependant (BHResponse StatusDependant a, a)
- joinBHResponse :: forall a parsingContext. BHRequest parsingContext (Either EsProtocolException (ParsedEsResponse a)) -> BHRequest parsingContext a
- newtype BHResponse parsingContext body = BHResponse {}
- decodeResponse :: FromJSON a => BHResponse StatusIndependant a -> Maybe a
- eitherDecodeResponse :: FromJSON a => BHResponse StatusIndependant a -> Either String a
- parseEsResponse :: FromJSON body => BHResponse parsingContext body -> Either EsProtocolException (ParsedEsResponse body)
- parseEsResponseWith :: (MonadThrow m, FromJSON body) => (body -> Either String parsed) -> BHResponse parsingContext body -> m parsed
- isVersionConflict :: BHResponse parsingContext a -> Bool
- isSuccess :: BHResponse parsingContext a -> Bool
- isCreated :: BHResponse parsingContext a -> Bool
- statusCodeIs :: (Int, Int) -> BHResponse parsingContext body -> Bool
- data EsProtocolException = EsProtocolException {}
- data EsResult a = EsResult {
- _index :: Text
- _type :: Maybe Text
- _id :: Text
- foundResult :: Maybe (EsResultFound a)
- data EsResultFound a = EsResultFound {
- _version :: DocVersion
- _source :: a
- data EsError = EsError {
- errorStatus :: Maybe Int
- errorMessage :: Text
- newtype Acknowledged = Acknowledged {}
- newtype Accepted = Accepted {
- isAccepted :: Bool
- data IgnoredBody = IgnoredBody
Documentation
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
data TimeInterval Source #
Instances
Read TimeInterval Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Units readsPrec :: Int -> ReadS TimeInterval # readList :: ReadS [TimeInterval] # | |
Show TimeInterval Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Units showsPrec :: Int -> TimeInterval -> ShowS # show :: TimeInterval -> String # showList :: [TimeInterval] -> ShowS # | |
Eq TimeInterval Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Units (==) :: TimeInterval -> TimeInterval -> Bool # (/=) :: TimeInterval -> TimeInterval -> Bool # |
parseStringInterval :: (Monad m, MonadFail m) => String -> m NominalDiffTime Source #
data TaskResponse a Source #
Instances
taskResponseTaskLens :: Lens' (TaskResponse a) (Task a) Source #
taskResponseReponseLens :: Lens' (TaskResponse a) (Maybe a) Source #
taskResponseErrorLens :: Lens' (TaskResponse a) (Maybe Object) Source #
Task | |
|
Instances
newtype TaskNodeId Source #
Instances
FromJSON TaskNodeId Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Task parseJSON :: Value -> Parser TaskNodeId # parseJSONList :: Value -> Parser [TaskNodeId] # | |
Show TaskNodeId Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Task showsPrec :: Int -> TaskNodeId -> ShowS # show :: TaskNodeId -> String # showList :: [TaskNodeId] -> ShowS # | |
Eq TaskNodeId Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Task (==) :: TaskNodeId -> TaskNodeId -> Bool # (/=) :: TaskNodeId -> TaskNodeId -> Bool # |
taskStatusLens :: Lens' (Task a) a Source #
Suggest | |
|
Instances
FromJSON Suggest Source # | |
ToJSON Suggest Source # | |
Generic Suggest Source # | |
Show Suggest Source # | |
Eq Suggest Source # | |
type Rep Suggest Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Suggest type Rep Suggest = D1 ('MetaData "Suggest" "Database.Bloodhound.Internal.Versions.Common.Types.Suggest" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) (C1 ('MetaCons "Suggest" 'PrefixI 'True) (S1 ('MetaSel ('Just "suggestText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "suggestName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "suggestType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SuggestType)))) |
data SuggestType Source #
Instances
data PhraseSuggester Source #
Instances
data PhraseSuggesterHighlighter Source #
Instances
data PhraseSuggesterCollate Source #
Instances
phraseSuggesterCollateParamsLens :: Lens' PhraseSuggesterCollate TemplateQueryKeyValuePairs Source #
data SuggestOptions Source #
Instances
FromJSON SuggestOptions Source # | |
Read SuggestOptions Source # | |
Show SuggestOptions Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Suggest showsPrec :: Int -> SuggestOptions -> ShowS # show :: SuggestOptions -> String # showList :: [SuggestOptions] -> ShowS # | |
Eq SuggestOptions Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Suggest (==) :: SuggestOptions -> SuggestOptions -> Bool # (/=) :: SuggestOptions -> SuggestOptions -> Bool # |
data SuggestResponse Source #
Instances
FromJSON SuggestResponse Source # | |
Read SuggestResponse Source # | |
Show SuggestResponse Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Suggest showsPrec :: Int -> SuggestResponse -> ShowS # show :: SuggestResponse -> String # showList :: [SuggestResponse] -> ShowS # | |
Eq SuggestResponse Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Suggest (==) :: SuggestResponse -> SuggestResponse -> Bool # (/=) :: SuggestResponse -> SuggestResponse -> Bool # |
data NamedSuggestionResponse Source #
Instances
data DirectGeneratorSuggestModeTypes Source #
DirectGeneratorSuggestModeMissing | |
DirectGeneratorSuggestModePopular | |
DirectGeneratorSuggestModeAlways |
Instances
FromJSON DirectGeneratorSuggestModeTypes Source # | |
ToJSON DirectGeneratorSuggestModeTypes Source # | |
Generic DirectGeneratorSuggestModeTypes Source # | |
Show DirectGeneratorSuggestModeTypes Source # | |
Eq DirectGeneratorSuggestModeTypes Source # | |
type Rep DirectGeneratorSuggestModeTypes Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Suggest type Rep DirectGeneratorSuggestModeTypes = D1 ('MetaData "DirectGeneratorSuggestModeTypes" "Database.Bloodhound.Internal.Versions.Common.Types.Suggest" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) (C1 ('MetaCons "DirectGeneratorSuggestModeMissing" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DirectGeneratorSuggestModePopular" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DirectGeneratorSuggestModeAlways" 'PrefixI 'False) (U1 :: Type -> Type))) |
data DirectGenerators Source #
Instances
SortMode
prescribes how to handle sorting array/multi-valued fields.
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.
The ignoreUnmapped
, when Just
field is used to set the elastic unmapped_type
DefaultSort | |
|
Instances
Show DefaultSort Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Sort showsPrec :: Int -> DefaultSort -> ShowS # show :: DefaultSort -> String # showList :: [DefaultSort] -> ShowS # | |
Eq DefaultSort Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Sort (==) :: DefaultSort -> DefaultSort -> Bool # (/=) :: DefaultSort -> DefaultSort -> Bool # |
SortOrder
is Ascending
or Descending
, as you might expect. These get
encoded into "asc" or "desc" when turned into JSON.
Missing
prescribes how to handle missing fields. A missing field can be
sorted last, first, or using a custom value as a substitute.
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
FsSnapshotRepo | |
|
Instances
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
Instances
newtype GenericSnapshotRepoSettings Source #
Opaque representation of snapshot repo settings. Instances of
SnapshotRepo
will produce this.
newtype RRGroupRefNum Source #
A group number for regex matching. Only values from 1-9 are
supported. Construct with mkRRGroupRefNum
Instances
Bounded RRGroupRefNum Source # | |
Show RRGroupRefNum Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Snapshots showsPrec :: Int -> RRGroupRefNum -> ShowS # show :: RRGroupRefNum -> String # showList :: [RRGroupRefNum] -> ShowS # | |
Eq RRGroupRefNum Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Snapshots (==) :: RRGroupRefNum -> RRGroupRefNum -> Bool # (/=) :: RRGroupRefNum -> RRGroupRefNum -> Bool # | |
Ord RRGroupRefNum Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Snapshots compare :: RRGroupRefNum -> RRGroupRefNum -> Ordering # (<) :: RRGroupRefNum -> RRGroupRefNum -> Bool # (<=) :: RRGroupRefNum -> RRGroupRefNum -> Bool # (>) :: RRGroupRefNum -> RRGroupRefNum -> Bool # (>=) :: RRGroupRefNum -> RRGroupRefNum -> Bool # max :: RRGroupRefNum -> RRGroupRefNum -> RRGroupRefNum # min :: RRGroupRefNum -> RRGroupRefNum -> RRGroupRefNum # |
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.
Instances
newtype RestoreRenamePattern Source #
Regex-stype pattern, e.g. "index_(.+)" to match index names
Instances
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.
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 |
Instances
Show RestoreRenameToken Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Snapshots showsPrec :: Int -> RestoreRenameToken -> ShowS # show :: RestoreRenameToken -> String # showList :: [RestoreRenameToken] -> ShowS # | |
Eq RestoreRenameToken Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Snapshots (==) :: RestoreRenameToken -> RestoreRenameToken -> Bool # (/=) :: RestoreRenameToken -> RestoreRenameToken -> Bool # |
data SnapshotCreateSettings Source #
SnapshotCreateSettings | |
|
Instances
data SnapshotInfo Source #
General information about the state of a snapshot. Has some
redundancies with SnapshotStatus
Instances
FromJSON SnapshotInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Snapshots parseJSON :: Value -> Parser SnapshotInfo # parseJSONList :: Value -> Parser [SnapshotInfo] # | |
Show SnapshotInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Snapshots showsPrec :: Int -> SnapshotInfo -> ShowS # show :: SnapshotInfo -> String # showList :: [SnapshotInfo] -> ShowS # | |
Eq SnapshotInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Snapshots (==) :: SnapshotInfo -> SnapshotInfo -> Bool # (/=) :: SnapshotInfo -> SnapshotInfo -> Bool # |
data SnapshotNodeVerification Source #
A node that has verified a snapshot
Instances
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
Instances
Show SnapshotPattern Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Snapshots showsPrec :: Int -> SnapshotPattern -> ShowS # show :: SnapshotPattern -> String # showList :: [SnapshotPattern] -> ShowS # | |
Eq SnapshotPattern Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Snapshots (==) :: SnapshotPattern -> SnapshotPattern -> Bool # (/=) :: SnapshotPattern -> SnapshotPattern -> Bool # |
class SnapshotRepo r where Source #
Law: fromGSnapshotRepo (toGSnapshotRepo r) == Right r
toGSnapshotRepo :: r -> GenericSnapshotRepo Source #
fromGSnapshotRepo :: GenericSnapshotRepo -> Either SnapshotRepoConversionError r Source #
data SnapshotRepoConversionError Source #
RepoTypeMismatch SnapshotRepoType SnapshotRepoType | Expected type and actual type |
OtherRepoConversionError Text |
newtype SnapshotRepoName Source #
The unique name of a snapshot repository.
Instances
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
Instances
data SnapshotRepoSelection Source #
Instances
newtype SnapshotRepoType Source #
Instances
newtype SnapshotRepoUpdateSettings Source #
SnapshotRepoUpdateSettings | |
|
data SnapshotRestoreSettings Source #
SnapshotRestoreSettings | |
|
Instances
data SnapshotSelection Source #
Instances
Show SnapshotSelection Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Snapshots showsPrec :: Int -> SnapshotSelection -> ShowS # show :: SnapshotSelection -> String # showList :: [SnapshotSelection] -> ShowS # | |
Eq SnapshotSelection Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Snapshots (==) :: SnapshotSelection -> SnapshotSelection -> Bool # (/=) :: SnapshotSelection -> SnapshotSelection -> Bool # |
data SnapshotShardFailure Source #
Instances
data SnapshotState Source #
SnapshotInit | |
SnapshotStarted | |
SnapshotSuccess | |
SnapshotFailed | |
SnapshotAborted | |
SnapshotMissing | |
SnapshotWaiting |
Instances
FromJSON SnapshotState Source # | |
Show SnapshotState Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Snapshots showsPrec :: Int -> SnapshotState -> ShowS # show :: SnapshotState -> String # showList :: [SnapshotState] -> ShowS # | |
Eq SnapshotState Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Snapshots (==) :: SnapshotState -> SnapshotState -> Bool # (/=) :: SnapshotState -> SnapshotState -> Bool # |
newtype SnapshotVerification Source #
The result of running verifySnapshotRepo
.
Instances
defaultSnapshotCreateSettings :: SnapshotCreateSettings Source #
Reasonable defaults for snapshot creation
- snapWaitForCompletion False
- snapIndices Nothing
- snapIgnoreUnavailable False
- snapIncludeGlobalState True
- snapPartial False
defaultSnapshotRepoUpdateSettings :: SnapshotRepoUpdateSettings Source #
Reasonable defaults for repo creation/update
- repoUpdateVerify True
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
mkRRGroupRefNum :: Int -> Maybe RRGroupRefNum Source #
Only allows valid group number references (1-9).
Optics
snapRestoreRenameReplacementLens :: Lens' SnapshotRestoreSettings (Maybe (NonEmpty RestoreRenameToken)) Source #
snapRestoreIndexSettingsOverridesLens :: Lens' SnapshotRestoreSettings (Maybe RestoreIndexSettings) Source #
snapRestoreIgnoreIndexSettingsLens :: Lens' SnapshotRestoreSettings (Maybe (NonEmpty Text)) Source #
data ExpandWildcards Source #
Instances
FromJSON ExpandWildcards Source # | |
ToJSON ExpandWildcards Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search toJSON :: ExpandWildcards -> Value # toEncoding :: ExpandWildcards -> Encoding # toJSONList :: [ExpandWildcards] -> Value # toEncodingList :: [ExpandWildcards] -> Encoding # omitField :: ExpandWildcards -> Bool # | |
Show ExpandWildcards Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search showsPrec :: Int -> ExpandWildcards -> ShowS # show :: ExpandWildcards -> String # showList :: [ExpandWildcards] -> ShowS # | |
Eq ExpandWildcards Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search (==) :: ExpandWildcards -> ExpandWildcards -> Bool # (/=) :: ExpandWildcards -> ExpandWildcards -> Bool # |
data GetTemplateScript Source #
Instances
FromJSON GetTemplateScript Source # | |
Show GetTemplateScript Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search showsPrec :: Int -> GetTemplateScript -> ShowS # show :: GetTemplateScript -> String # showList :: [GetTemplateScript] -> ShowS # | |
Eq GetTemplateScript Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search (==) :: GetTemplateScript -> GetTemplateScript -> Bool # (/=) :: GetTemplateScript -> GetTemplateScript -> Bool # |
data PatternOrPatterns Source #
Instances
ToJSON PatternOrPatterns Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search toJSON :: PatternOrPatterns -> Value # toEncoding :: PatternOrPatterns -> Encoding # toJSONList :: [PatternOrPatterns] -> Value # toEncodingList :: [PatternOrPatterns] -> Encoding # omitField :: PatternOrPatterns -> Bool # | |
Read PatternOrPatterns Source # | |
Show PatternOrPatterns Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search showsPrec :: Int -> PatternOrPatterns -> ShowS # show :: PatternOrPatterns -> String # showList :: [PatternOrPatterns] -> ShowS # | |
Eq PatternOrPatterns Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search (==) :: PatternOrPatterns -> PatternOrPatterns -> Bool # (/=) :: PatternOrPatterns -> PatternOrPatterns -> Bool # |
Search | |
|
data SearchResult a Source #
SearchResult | |
|
Instances
FromJSON a => FromJSON (SearchResult a) Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search parseJSON :: Value -> Parser (SearchResult a) # parseJSONList :: Value -> Parser [SearchResult a] # omittedField :: Maybe (SearchResult a) # | |
Show a => Show (SearchResult a) Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search showsPrec :: Int -> SearchResult a -> ShowS # show :: SearchResult a -> String # showList :: [SearchResult a] -> ShowS # | |
Eq a => Eq (SearchResult a) Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search (==) :: SearchResult a -> SearchResult a -> Bool # (/=) :: SearchResult a -> SearchResult a -> Bool # |
data SearchTemplate Source #
Instances
ToJSON SearchTemplate Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search toJSON :: SearchTemplate -> Value # toEncoding :: SearchTemplate -> Encoding # toJSONList :: [SearchTemplate] -> Value # toEncodingList :: [SearchTemplate] -> Encoding # omitField :: SearchTemplate -> Bool # | |
Show SearchTemplate Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search showsPrec :: Int -> SearchTemplate -> ShowS # show :: SearchTemplate -> String # showList :: [SearchTemplate] -> ShowS # | |
Eq SearchTemplate Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search (==) :: SearchTemplate -> SearchTemplate -> Bool # (/=) :: SearchTemplate -> SearchTemplate -> Bool # |
newtype SearchTemplateId Source #
Instances
ToJSON SearchTemplateId Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search toJSON :: SearchTemplateId -> Value # toEncoding :: SearchTemplateId -> Encoding # toJSONList :: [SearchTemplateId] -> Value # toEncodingList :: [SearchTemplateId] -> Encoding # omitField :: SearchTemplateId -> Bool # | |
Show SearchTemplateId Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search showsPrec :: Int -> SearchTemplateId -> ShowS # show :: SearchTemplateId -> String # showList :: [SearchTemplateId] -> ShowS # | |
Eq SearchTemplateId Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search (==) :: SearchTemplateId -> SearchTemplateId -> Bool # (/=) :: SearchTemplateId -> SearchTemplateId -> Bool # |
newtype SearchTemplateSource Source #
Instances
data SearchType Source #
Instances
FromJSON SearchType Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search parseJSON :: Value -> Parser SearchType # parseJSONList :: Value -> Parser [SearchType] # | |
ToJSON SearchType Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search toJSON :: SearchType -> Value # toEncoding :: SearchType -> Encoding # toJSONList :: [SearchType] -> Value # toEncodingList :: [SearchType] -> Encoding # omitField :: SearchType -> Bool # | |
Show SearchType Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search showsPrec :: Int -> SearchType -> ShowS # show :: SearchType -> String # showList :: [SearchType] -> ShowS # | |
Eq SearchType Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Search (==) :: SearchType -> SearchType -> Bool # (/=) :: SearchType -> SearchType -> Bool # |
TimeUnitDays | |
TimeUnitHours | |
TimeUnitMinutes | |
TimeUnitSeconds | |
TimeUnitMilliseconds | |
TimeUnitMicroseconds | |
TimeUnitNanoseconds |
type TrackSortScores = Bool Source #
Optics
timedOutLens :: Lens' (SearchResult a) Bool Source #
shardsLens :: Lens' (SearchResult a) ShardResult Source #
searchHitsLens :: Lens' (SearchResult a) (SearchHits a) Source #
scrollIdLens :: Lens' (SearchResult a) (Maybe ScrollId) Source #
data ReindexRequest Source #
Instances
data ReindexConflicts Source #
Instances
data ReindexSource Source #
Elasticsearch also supports reindex from remote, it could be added here if required
Instances
data ReindexSlice Source #
Instances
data ReindexDest Source #
Instances
data VersionType Source #
Instances
data ReindexOpType Source #
Instances
data ReindexScript Source #
Instances
mkReindexRequest :: IndexName -> IndexName -> ReindexRequest Source #
data ReindexResponse Source #
Instances
newtype ScriptFields Source #
Instances
FromJSON ScriptFields Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Script parseJSON :: Value -> Parser ScriptFields # parseJSONList :: Value -> Parser [ScriptFields] # | |
ToJSON ScriptFields Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Script toJSON :: ScriptFields -> Value # toEncoding :: ScriptFields -> Encoding # toJSONList :: [ScriptFields] -> Value # toEncodingList :: [ScriptFields] -> Encoding # omitField :: ScriptFields -> Bool # | |
Show ScriptFields Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Script showsPrec :: Int -> ScriptFields -> ShowS # show :: ScriptFields -> String # showList :: [ScriptFields] -> ShowS # | |
Eq ScriptFields Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Script (==) :: ScriptFields -> ScriptFields -> Bool # (/=) :: ScriptFields -> ScriptFields -> Bool # |
type ScriptFieldValue = Value Source #
data ScriptSource Source #
Instances
Instances
FromJSON Script Source # | |
ToJSON Script Source # | |
Generic Script Source # | |
Show Script Source # | |
Eq Script Source # | |
type Rep Script Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Script type Rep Script = D1 ('MetaData "Script" "Database.Bloodhound.Internal.Versions.Common.Types.Script" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) (C1 ('MetaCons "Script" 'PrefixI 'True) (S1 ('MetaSel ('Just "scriptLanguage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ScriptLanguage)) :*: (S1 ('MetaSel ('Just "scriptSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScriptSource) :*: S1 ('MetaSel ('Just "scriptParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ScriptParams))))) |
newtype ScriptLanguage Source #
Instances
FromJSON ScriptLanguage Source # | |
ToJSON ScriptLanguage Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Script toJSON :: ScriptLanguage -> Value # toEncoding :: ScriptLanguage -> Encoding # toJSONList :: [ScriptLanguage] -> Value # toEncodingList :: [ScriptLanguage] -> Encoding # omitField :: ScriptLanguage -> Bool # | |
Show ScriptLanguage Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Script showsPrec :: Int -> ScriptLanguage -> ShowS # show :: ScriptLanguage -> String # showList :: [ScriptLanguage] -> ShowS # | |
Eq ScriptLanguage Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Script (==) :: ScriptLanguage -> ScriptLanguage -> Bool # (/=) :: ScriptLanguage -> ScriptLanguage -> Bool # |
newtype ScriptParams Source #
Instances
FromJSON ScriptParams Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Script parseJSON :: Value -> Parser ScriptParams # parseJSONList :: Value -> Parser [ScriptParams] # | |
ToJSON ScriptParams Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Script toJSON :: ScriptParams -> Value # toEncoding :: ScriptParams -> Encoding # toJSONList :: [ScriptParams] -> Value # toEncodingList :: [ScriptParams] -> Encoding # omitField :: ScriptParams -> Bool # | |
Show ScriptParams Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Script showsPrec :: Int -> ScriptParams -> ShowS # show :: ScriptParams -> String # showList :: [ScriptParams] -> ShowS # | |
Eq ScriptParams Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Script (==) :: ScriptParams -> ScriptParams -> Bool # (/=) :: ScriptParams -> ScriptParams -> Bool # |
type ScriptParamValue = Value Source #
Instances
FromJSON BoostMode Source # | |
ToJSON BoostMode Source # | |
Generic BoostMode Source # | |
Show BoostMode Source # | |
Eq BoostMode Source # | |
type Rep BoostMode Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Script type Rep BoostMode = D1 ('MetaData "BoostMode" "Database.Bloodhound.Internal.Versions.Common.Types.Script" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) ((C1 ('MetaCons "BoostModeMultiply" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BoostModeReplace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BoostModeSum" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "BoostModeAvg" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BoostModeMax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BoostModeMin" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Instances
FromJSON ScoreMode Source # | |
ToJSON ScoreMode Source # | |
Generic ScoreMode Source # | |
Show ScoreMode Source # | |
Eq ScoreMode Source # | |
type Rep ScoreMode Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Script type Rep ScoreMode = D1 ('MetaData "ScoreMode" "Database.Bloodhound.Internal.Versions.Common.Types.Script" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) ((C1 ('MetaCons "ScoreModeMultiply" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ScoreModeSum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScoreModeAvg" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ScoreModeFirst" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ScoreModeMax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScoreModeMin" 'PrefixI 'False) (U1 :: Type -> Type)))) |
data FunctionScoreFunction Source #
FunctionScoreFunctionScript Script | |
FunctionScoreFunctionRandom Seed | |
FunctionScoreFunctionFieldValueFactor FieldValueFactor |
Instances
data FieldValueFactor Source #
Instances
data FactorModifier Source #
FactorModifierNone | |
FactorModifierLog | |
FactorModifierLog1p | |
FactorModifierLog2p | |
FactorModifierLn | |
FactorModifierLn1p | |
FactorModifierLn2p | |
FactorModifierSquare | |
FactorModifierSqrt | |
FactorModifierReciprocal |
Instances
newtype FactorMissingFieldValue Source #
Instances
data WildcardQuery Source #
Instances
data FieldOrFields Source #
Instances
data SimpleQueryFlag Source #
Instances
data SimpleQueryStringQuery Source #
Instances
data RegexpFlag Source #
Instances
data RegexpFlags Source #
Instances
data RegexpQuery Source #
Instances
newtype GreaterThan Source #
Instances
newtype GreaterThanD Source #
Instances
newtype GreaterThanEq Source #
Instances
newtype GreaterThanEqD Source #
Instances
Instances
Generic LessThan Source # | |
Show LessThan Source # | |
Eq LessThan Source # | |
type Rep LessThan Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Query.Range type Rep LessThan = D1 ('MetaData "LessThan" "Database.Bloodhound.Internal.Versions.Common.Types.Query.Range" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'True) (C1 ('MetaCons "LessThan" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))) |
Instances
Generic LessThanD Source # | |
Show LessThanD Source # | |
Eq LessThanD Source # | |
type Rep LessThanD Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Query.Range type Rep LessThanD = D1 ('MetaData "LessThanD" "Database.Bloodhound.Internal.Versions.Common.Types.Query.Range" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'True) (C1 ('MetaCons "LessThanD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime))) |
newtype LessThanEq Source #
Instances
newtype LessThanEqD Source #
Instances
data RangeQuery Source #
Instances
data RangeValue Source #
Instances
mkRangeQuery :: FieldName -> RangeValue -> RangeQuery Source #
data QueryStringQuery Source #
Instances
data PrefixQuery Source #
Instances
data MoreLikeThisFieldQuery Source #
Instances
data MoreLikeThisQuery Source #
Instances
data MatchQuery Source #
Instances
data MatchQueryType Source #
Instances
data MultiMatchQuery Source #
Instances
data MultiMatchQueryType Source #
MultiMatchBestFields | |
MultiMatchMostFields | |
MultiMatchCrossFields | |
MultiMatchPhrase | |
MultiMatchPhrasePrefix |
Instances
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
.
data FuzzyQuery Source #
Instances
data FuzzyLikeFieldQuery Source #
Instances
data FuzzyLikeThisQuery Source #
Instances
data BooleanOperator Source #
BooleanOperator
is the usual And/Or operators with an ES compatible
JSON encoding baked in. Used all over the place.
Instances
Fuzziness value as a number or AUTO
.
See:
https://www.elastic.co/guide/en/elasticsearch/reference/current/common-options.html#fuzziness
Instances
FromJSON Fuzziness Source # | |
ToJSON Fuzziness Source # | |
Generic Fuzziness Source # | |
Show Fuzziness Source # | |
Eq Fuzziness Source # | |
type Rep Fuzziness Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Query.Commons type Rep Fuzziness = D1 ('MetaData "Fuzziness" "Database.Bloodhound.Internal.Versions.Common.Types.Query.Commons" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) (C1 ('MetaCons "Fuzziness" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: C1 ('MetaCons "FuzzinessAuto" 'PrefixI 'False) (U1 :: Type -> Type)) |
data ZeroTermsQuery Source #
Instances
data CommonMinimumMatch Source #
Instances
data CommonTermsQuery Source #
Instances
data MinimumMatchHighLow Source #
Instances
module Data.Aeson.KeyMap
Instances
Instances
data BoostingQuery Source #
Instances
data ComponentFunctionScoreFunction Source #
Instances
data DisMaxQuery Source #
Instances
Instances
FromJSON Distance Source # | |
ToJSON Distance Source # | |
Generic Distance Source # | |
Show Distance Source # | |
Eq Distance Source # | |
type Rep Distance Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Query type Rep Distance = D1 ('MetaData "Distance" "Database.Bloodhound.Internal.Versions.Common.Types.Query" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) (C1 ('MetaCons "Distance" 'PrefixI 'True) (S1 ('MetaSel ('Just "coefficient") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "unit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DistanceUnit))) |
data DistanceRange Source #
Instances
data DistanceType Source #
Instances
data DistanceUnit Source #
Instances
As of Elastic 2.0, Filters
are just Queries
housed in a
Bool Query, and flagged in a different context.
data FunctionScoreFunctions Source #
FunctionScoreSingle FunctionScoreFunction | |
FunctionScoreMultiple (NonEmpty ComponentFunctionScoreFunction) |
Instances
data FunctionScoreQuery Source #
Instances
data GeoBoundingBox Source #
Instances
data GeoBoundingBoxConstraint Source #
Instances
data GeoFilterType Source #
Instances
Instances
ToJSON GeoPoint Source # | |
Generic GeoPoint Source # | |
Show GeoPoint Source # | |
Eq GeoPoint Source # | |
type Rep GeoPoint Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Query type Rep GeoPoint = D1 ('MetaData "GeoPoint" "Database.Bloodhound.Internal.Versions.Common.Types.Query" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) (C1 ('MetaCons "GeoPoint" 'PrefixI 'True) (S1 ('MetaSel ('Just "geoField") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FieldName) :*: S1 ('MetaSel ('Just "latLon") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LatLon))) |
data HasChildQuery Source #
Instances
data HasParentQuery Source #
Instances
data IndicesQuery Source #
Instances
Instances
FromJSON InnerHits Source # | |
ToJSON InnerHits Source # | |
Generic InnerHits Source # | |
Show InnerHits Source # | |
Eq InnerHits Source # | |
type Rep InnerHits Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Query type Rep InnerHits = D1 ('MetaData "InnerHits" "Database.Bloodhound.Internal.Versions.Common.Types.Query" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) (C1 ('MetaCons "InnerHits" 'PrefixI 'True) (S1 ('MetaSel ('Just "innerHitsFrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer)) :*: S1 ('MetaSel ('Just "innerHitsSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer)))) |
Instances
FromJSON LatLon Source # | |
ToJSON LatLon Source # | |
Generic LatLon Source # | |
Show LatLon Source # | |
Eq LatLon Source # | |
type Rep LatLon Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Query type Rep LatLon = D1 ('MetaData "LatLon" "Database.Bloodhound.Internal.Versions.Common.Types.Query" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) (C1 ('MetaCons "LatLon" 'PrefixI 'True) (S1 ('MetaSel ('Just "lat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "lon") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))) |
data NestedQuery Source #
Instances
data OptimizeBbox Source #
Instances
Instances
data RangeExecution Source #
Instances
Instances
FromJSON ScoreType Source # | |
ToJSON ScoreType Source # | |
Generic ScoreType Source # | |
Show ScoreType Source # | |
Eq ScoreType Source # | |
type Rep ScoreType Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Query type Rep ScoreType = D1 ('MetaData "ScoreType" "Database.Bloodhound.Internal.Versions.Common.Types.Query" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) ((C1 ('MetaCons "ScoreTypeMax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScoreTypeSum" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ScoreTypeAvg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScoreTypeNone" 'PrefixI 'False) (U1 :: Type -> Type))) |
newtype TemplateQueryKeyValuePairs Source #
Instances
type TemplateQueryValue = Text Source #
Instances
FromJSON Term Source # | |
ToJSON Term Source # | |
Generic Term Source # | |
Show Term Source # | |
Eq Term Source # | |
type Rep Term Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Query type Rep Term = D1 ('MetaData "Term" "Database.Bloodhound.Internal.Versions.Common.Types.Query" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) (C1 ('MetaCons "Term" 'PrefixI 'True) (S1 ('MetaSel ('Just "termField") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Key) :*: S1 ('MetaSel ('Just "termValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
defaultCache :: Cache Source #
showDistanceUnit :: DistanceUnit -> Text Source #
data PointInTime Source #
Instances
FromJSON PointInTime Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.PointInTime parseJSON :: Value -> Parser PointInTime # parseJSONList :: Value -> Parser [PointInTime] # | |
ToJSON PointInTime Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.PointInTime toJSON :: PointInTime -> Value # toEncoding :: PointInTime -> Encoding # toJSONList :: [PointInTime] -> Value # toEncodingList :: [PointInTime] -> Encoding # omitField :: PointInTime -> Bool # | |
Show PointInTime Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.PointInTime showsPrec :: Int -> PointInTime -> ShowS # show :: PointInTime -> String # showList :: [PointInTime] -> ShowS # | |
Eq PointInTime Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.PointInTime (==) :: PointInTime -> PointInTime -> Bool # (/=) :: PointInTime -> PointInTime -> Bool # |
data BoundTransportAddress Source #
Instances
Typically a 7 character hex string.
CPUInfo | |
|
newtype ClusterName Source #
Instances
FromJSON ClusterName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser ClusterName # parseJSONList :: Value -> Parser [ClusterName] # | |
Show ClusterName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> ClusterName -> ShowS # show :: ClusterName -> String # showList :: [ClusterName] -> ShowS # | |
Eq ClusterName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: ClusterName -> ClusterName -> Bool # (/=) :: ClusterName -> ClusterName -> Bool # | |
Ord ClusterName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes compare :: ClusterName -> ClusterName -> Ordering # (<) :: ClusterName -> ClusterName -> Bool # (<=) :: ClusterName -> ClusterName -> Bool # (>) :: ClusterName -> ClusterName -> Bool # (>=) :: ClusterName -> ClusterName -> Bool # max :: ClusterName -> ClusterName -> ClusterName # min :: ClusterName -> ClusterName -> ClusterName # |
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.
newtype EsPassword Source #
Password type used for HTTP Basic authentication. See basicAuthHook
.
Instances
Read EsPassword Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes readsPrec :: Int -> ReadS EsPassword # readList :: ReadS [EsPassword] # readPrec :: ReadPrec EsPassword # readListPrec :: ReadPrec [EsPassword] # | |
Show EsPassword Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> EsPassword -> ShowS # show :: EsPassword -> String # showList :: [EsPassword] -> ShowS # | |
Eq EsPassword Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: EsPassword -> EsPassword -> Bool # (/=) :: EsPassword -> EsPassword -> Bool # |
newtype EsUsername Source #
Username type used for HTTP Basic authentication. See basicAuthHook
.
Instances
Read EsUsername Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes readsPrec :: Int -> ReadS EsUsername # readList :: ReadS [EsUsername] # readPrec :: ReadPrec EsUsername # readListPrec :: ReadPrec [EsUsername] # | |
Show EsUsername Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> EsUsername -> ShowS # show :: EsUsername -> String # showList :: [EsUsername] -> ShowS # | |
Eq EsUsername Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: EsUsername -> EsUsername -> Bool # (/=) :: EsUsername -> EsUsername -> Bool # |
newtype FullNodeId Source #
Unique, automatically-generated name assigned to nodes that are usually returned in node-oriented APIs.
Instances
FromJSON FullNodeId Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser FullNodeId # parseJSONList :: Value -> Parser [FullNodeId] # | |
Show FullNodeId Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> FullNodeId -> ShowS # show :: FullNodeId -> String # showList :: [FullNodeId] -> ShowS # | |
Eq FullNodeId Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: FullNodeId -> FullNodeId -> Bool # (/=) :: FullNodeId -> FullNodeId -> Bool # | |
Ord FullNodeId Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes compare :: FullNodeId -> FullNodeId -> Ordering # (<) :: FullNodeId -> FullNodeId -> Bool # (<=) :: FullNodeId -> FullNodeId -> Bool # (>) :: FullNodeId -> FullNodeId -> Bool # (>=) :: FullNodeId -> FullNodeId -> Bool # max :: FullNodeId -> FullNodeId -> FullNodeId # min :: FullNodeId -> FullNodeId -> FullNodeId # |
data InitialShardCount Source #
Instances
data JVMBufferPoolStats Source #
Instances
newtype JVMGCCollector Source #
Instances
FromJSON JVMGCCollector Source # | |
Show JVMGCCollector Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> JVMGCCollector -> ShowS # show :: JVMGCCollector -> String # showList :: [JVMGCCollector] -> ShowS # | |
Eq JVMGCCollector Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: JVMGCCollector -> JVMGCCollector -> Bool # (/=) :: JVMGCCollector -> JVMGCCollector -> Bool # |
data JVMGCStats Source #
Instances
FromJSON JVMGCStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser JVMGCStats # parseJSONList :: Value -> Parser [JVMGCStats] # | |
Show JVMGCStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> JVMGCStats -> ShowS # show :: JVMGCStats -> String # showList :: [JVMGCStats] -> ShowS # | |
Eq JVMGCStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: JVMGCStats -> JVMGCStats -> Bool # (/=) :: JVMGCStats -> JVMGCStats -> Bool # |
data JVMMemoryInfo Source #
Instances
FromJSON JVMMemoryInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser JVMMemoryInfo # parseJSONList :: Value -> Parser [JVMMemoryInfo] # | |
Show JVMMemoryInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> JVMMemoryInfo -> ShowS # show :: JVMMemoryInfo -> String # showList :: [JVMMemoryInfo] -> ShowS # | |
Eq JVMMemoryInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: JVMMemoryInfo -> JVMMemoryInfo -> Bool # (/=) :: JVMMemoryInfo -> JVMMemoryInfo -> Bool # |
newtype JVMMemoryPool Source #
Instances
FromJSON JVMMemoryPool Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser JVMMemoryPool # parseJSONList :: Value -> Parser [JVMMemoryPool] # | |
Show JVMMemoryPool Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> JVMMemoryPool -> ShowS # show :: JVMMemoryPool -> String # showList :: [JVMMemoryPool] -> ShowS # | |
Eq JVMMemoryPool Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: JVMMemoryPool -> JVMMemoryPool -> Bool # (/=) :: JVMMemoryPool -> JVMMemoryPool -> Bool # |
data JVMPoolStats Source #
Instances
FromJSON JVMPoolStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser JVMPoolStats # parseJSONList :: Value -> Parser [JVMPoolStats] # | |
Show JVMPoolStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> JVMPoolStats -> ShowS # show :: JVMPoolStats -> String # showList :: [JVMPoolStats] -> ShowS # | |
Eq JVMPoolStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: JVMPoolStats -> JVMPoolStats -> Bool # (/=) :: JVMPoolStats -> JVMPoolStats -> Bool # |
newtype JVMVersion Source #
We cannot parse JVM version numbers and we're not going to try.
Instances
FromJSON JVMVersion Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser JVMVersion # parseJSONList :: Value -> Parser [JVMVersion] # | |
Show JVMVersion Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> JVMVersion -> ShowS # show :: JVMVersion -> String # showList :: [JVMVersion] -> ShowS # | |
Eq JVMVersion Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: JVMVersion -> JVMVersion -> Bool # (/=) :: JVMVersion -> JVMVersion -> Bool # |
LoadAvgs | |
|
newtype MacAddress Source #
Instances
FromJSON MacAddress Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser MacAddress # parseJSONList :: Value -> Parser [MacAddress] # | |
Show MacAddress Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> MacAddress -> ShowS # show :: MacAddress -> String # showList :: [MacAddress] -> ShowS # | |
Eq MacAddress Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: MacAddress -> MacAddress -> Bool # (/=) :: MacAddress -> MacAddress -> Bool # | |
Ord MacAddress Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes compare :: MacAddress -> MacAddress -> Ordering # (<) :: MacAddress -> MacAddress -> Bool # (<=) :: MacAddress -> MacAddress -> Bool # (>) :: MacAddress -> MacAddress -> Bool # (>=) :: MacAddress -> MacAddress -> Bool # max :: MacAddress -> MacAddress -> MacAddress # min :: MacAddress -> MacAddress -> MacAddress # |
newtype NetworkInterfaceName Source #
Instances
data NodeAttrFilter Source #
Instances
Show NodeAttrFilter Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeAttrFilter -> ShowS # show :: NodeAttrFilter -> String # showList :: [NodeAttrFilter] -> ShowS # | |
Eq NodeAttrFilter Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeAttrFilter -> NodeAttrFilter -> Bool # (/=) :: NodeAttrFilter -> NodeAttrFilter -> Bool # | |
Ord NodeAttrFilter Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes compare :: NodeAttrFilter -> NodeAttrFilter -> Ordering # (<) :: NodeAttrFilter -> NodeAttrFilter -> Bool # (<=) :: NodeAttrFilter -> NodeAttrFilter -> Bool # (>) :: NodeAttrFilter -> NodeAttrFilter -> Bool # (>=) :: NodeAttrFilter -> NodeAttrFilter -> Bool # max :: NodeAttrFilter -> NodeAttrFilter -> NodeAttrFilter # min :: NodeAttrFilter -> NodeAttrFilter -> NodeAttrFilter # |
newtype NodeAttrName Source #
Instances
Show NodeAttrName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeAttrName -> ShowS # show :: NodeAttrName -> String # showList :: [NodeAttrName] -> ShowS # | |
Eq NodeAttrName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeAttrName -> NodeAttrName -> Bool # (/=) :: NodeAttrName -> NodeAttrName -> Bool # | |
Ord NodeAttrName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes compare :: NodeAttrName -> NodeAttrName -> Ordering # (<) :: NodeAttrName -> NodeAttrName -> Bool # (<=) :: NodeAttrName -> NodeAttrName -> Bool # (>) :: NodeAttrName -> NodeAttrName -> Bool # (>=) :: NodeAttrName -> NodeAttrName -> Bool # max :: NodeAttrName -> NodeAttrName -> NodeAttrName # min :: NodeAttrName -> NodeAttrName -> NodeAttrName # |
data NodeBreakerStats Source #
Instances
FromJSON NodeBreakerStats Source # | |
Show NodeBreakerStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeBreakerStats -> ShowS # show :: NodeBreakerStats -> String # showList :: [NodeBreakerStats] -> ShowS # | |
Eq NodeBreakerStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeBreakerStats -> NodeBreakerStats -> Bool # (/=) :: NodeBreakerStats -> NodeBreakerStats -> Bool # |
data NodeBreakersStats Source #
Instances
FromJSON NodeBreakersStats Source # | |
Show NodeBreakersStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeBreakersStats -> ShowS # show :: NodeBreakersStats -> String # showList :: [NodeBreakersStats] -> ShowS # | |
Eq NodeBreakersStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeBreakersStats -> NodeBreakersStats -> Bool # (/=) :: NodeBreakersStats -> NodeBreakersStats -> Bool # |
data NodeDataPathStats Source #
Instances
FromJSON NodeDataPathStats Source # | |
Show NodeDataPathStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeDataPathStats -> ShowS # show :: NodeDataPathStats -> String # showList :: [NodeDataPathStats] -> ShowS # | |
Eq NodeDataPathStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeDataPathStats -> NodeDataPathStats -> Bool # (/=) :: NodeDataPathStats -> NodeDataPathStats -> Bool # |
data NodeFSStats Source #
Instances
FromJSON NodeFSStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser NodeFSStats # parseJSONList :: Value -> Parser [NodeFSStats] # | |
Show NodeFSStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeFSStats -> ShowS # show :: NodeFSStats -> String # showList :: [NodeFSStats] -> ShowS # | |
Eq NodeFSStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeFSStats -> NodeFSStats -> Bool # (/=) :: NodeFSStats -> NodeFSStats -> Bool # |
data NodeFSTotalStats Source #
Instances
FromJSON NodeFSTotalStats Source # | |
Show NodeFSTotalStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeFSTotalStats -> ShowS # show :: NodeFSTotalStats -> String # showList :: [NodeFSTotalStats] -> ShowS # | |
Eq NodeFSTotalStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeFSTotalStats -> NodeFSTotalStats -> Bool # (/=) :: NodeFSTotalStats -> NodeFSTotalStats -> Bool # |
data NodeHTTPInfo Source #
Instances
FromJSON NodeHTTPInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser NodeHTTPInfo # parseJSONList :: Value -> Parser [NodeHTTPInfo] # | |
Show NodeHTTPInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeHTTPInfo -> ShowS # show :: NodeHTTPInfo -> String # showList :: [NodeHTTPInfo] -> ShowS # | |
Eq NodeHTTPInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeHTTPInfo -> NodeHTTPInfo -> Bool # (/=) :: NodeHTTPInfo -> NodeHTTPInfo -> Bool # |
data NodeHTTPStats Source #
Instances
FromJSON NodeHTTPStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser NodeHTTPStats # parseJSONList :: Value -> Parser [NodeHTTPStats] # | |
Show NodeHTTPStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeHTTPStats -> ShowS # show :: NodeHTTPStats -> String # showList :: [NodeHTTPStats] -> ShowS # | |
Eq NodeHTTPStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeHTTPStats -> NodeHTTPStats -> Bool # (/=) :: NodeHTTPStats -> NodeHTTPStats -> Bool # |
data NodeIndicesStats Source #
Instances
FromJSON NodeIndicesStats Source # | |
Show NodeIndicesStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeIndicesStats -> ShowS # show :: NodeIndicesStats -> String # showList :: [NodeIndicesStats] -> ShowS # | |
Eq NodeIndicesStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeIndicesStats -> NodeIndicesStats -> Bool # (/=) :: NodeIndicesStats -> NodeIndicesStats -> Bool # |
NodeInfo | |
|
data NodeJVMInfo Source #
NodeJVMInfo | |
|
Instances
FromJSON NodeJVMInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser NodeJVMInfo # parseJSONList :: Value -> Parser [NodeJVMInfo] # | |
Show NodeJVMInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeJVMInfo -> ShowS # show :: NodeJVMInfo -> String # showList :: [NodeJVMInfo] -> ShowS # | |
Eq NodeJVMInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeJVMInfo -> NodeJVMInfo -> Bool # (/=) :: NodeJVMInfo -> NodeJVMInfo -> Bool # |
data NodeJVMStats Source #
Instances
FromJSON NodeJVMStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser NodeJVMStats # parseJSONList :: Value -> Parser [NodeJVMStats] # | |
Show NodeJVMStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeJVMStats -> ShowS # show :: NodeJVMStats -> String # showList :: [NodeJVMStats] -> ShowS # | |
Eq NodeJVMStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeJVMStats -> NodeJVMStats -> Bool # (/=) :: NodeJVMStats -> NodeJVMStats -> Bool # |
A human-readable node name that is supplied by the user in the node config or automatically generated by Elasticsearch.
data NodeNetworkInfo Source #
Instances
FromJSON NodeNetworkInfo Source # | |
Show NodeNetworkInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeNetworkInfo -> ShowS # show :: NodeNetworkInfo -> String # showList :: [NodeNetworkInfo] -> ShowS # | |
Eq NodeNetworkInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeNetworkInfo -> NodeNetworkInfo -> Bool # (/=) :: NodeNetworkInfo -> NodeNetworkInfo -> Bool # |
data NodeNetworkInterface Source #
Instances
data NodeNetworkStats Source #
Instances
FromJSON NodeNetworkStats Source # | |
Show NodeNetworkStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeNetworkStats -> ShowS # show :: NodeNetworkStats -> String # showList :: [NodeNetworkStats] -> ShowS # | |
Eq NodeNetworkStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeNetworkStats -> NodeNetworkStats -> Bool # (/=) :: NodeNetworkStats -> NodeNetworkStats -> Bool # |
data NodeOSInfo Source #
Instances
FromJSON NodeOSInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser NodeOSInfo # parseJSONList :: Value -> Parser [NodeOSInfo] # | |
Show NodeOSInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeOSInfo -> ShowS # show :: NodeOSInfo -> String # showList :: [NodeOSInfo] -> ShowS # | |
Eq NodeOSInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeOSInfo -> NodeOSInfo -> Bool # (/=) :: NodeOSInfo -> NodeOSInfo -> Bool # |
data NodeOSStats Source #
Instances
FromJSON NodeOSStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser NodeOSStats # parseJSONList :: Value -> Parser [NodeOSStats] # | |
Show NodeOSStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeOSStats -> ShowS # show :: NodeOSStats -> String # showList :: [NodeOSStats] -> ShowS # | |
Eq NodeOSStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeOSStats -> NodeOSStats -> Bool # (/=) :: NodeOSStats -> NodeOSStats -> Bool # |
data NodePluginInfo Source #
NodePluginInfo | |
|
Instances
FromJSON NodePluginInfo Source # | |
Show NodePluginInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodePluginInfo -> ShowS # show :: NodePluginInfo -> String # showList :: [NodePluginInfo] -> ShowS # | |
Eq NodePluginInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodePluginInfo -> NodePluginInfo -> Bool # (/=) :: NodePluginInfo -> NodePluginInfo -> Bool # |
data NodeProcessInfo Source #
Instances
FromJSON NodeProcessInfo Source # | |
Show NodeProcessInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeProcessInfo -> ShowS # show :: NodeProcessInfo -> String # showList :: [NodeProcessInfo] -> ShowS # | |
Eq NodeProcessInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeProcessInfo -> NodeProcessInfo -> Bool # (/=) :: NodeProcessInfo -> NodeProcessInfo -> Bool # |
data NodeProcessStats Source #
Instances
FromJSON NodeProcessStats Source # | |
Show NodeProcessStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeProcessStats -> ShowS # show :: NodeProcessStats -> String # showList :: [NodeProcessStats] -> ShowS # | |
Eq NodeProcessStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeProcessStats -> NodeProcessStats -> Bool # (/=) :: NodeProcessStats -> NodeProcessStats -> Bool # |
data NodeSelection Source #
NodeSelection
is used for most cluster APIs. See here for more details.
LocalNode | Whatever node receives this request |
NodeList (NonEmpty NodeSelector) | |
AllNodes |
Instances
Show NodeSelection Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeSelection -> ShowS # show :: NodeSelection -> String # showList :: [NodeSelection] -> ShowS # | |
Eq NodeSelection Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeSelection -> NodeSelection -> Bool # (/=) :: NodeSelection -> NodeSelection -> Bool # |
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.
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. |
Instances
Show NodeSelector Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeSelector -> ShowS # show :: NodeSelector -> String # showList :: [NodeSelector] -> ShowS # | |
Eq NodeSelector Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeSelector -> NodeSelector -> Bool # (/=) :: NodeSelector -> NodeSelector -> Bool # |
data NodeThreadPoolInfo Source #
Instances
data NodeThreadPoolStats Source #
Instances
data NodeTransportInfo Source #
Instances
FromJSON NodeTransportInfo Source # | |
Show NodeTransportInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodeTransportInfo -> ShowS # show :: NodeTransportInfo -> String # showList :: [NodeTransportInfo] -> ShowS # | |
Eq NodeTransportInfo Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodeTransportInfo -> NodeTransportInfo -> Bool # (/=) :: NodeTransportInfo -> NodeTransportInfo -> Bool # |
data NodeTransportStats Source #
Instances
data NodesStats Source #
Instances
FromJSON NodesStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser NodesStats # parseJSONList :: Value -> Parser [NodesStats] # | |
Show NodesStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> NodesStats -> ShowS # show :: NodesStats -> String # showList :: [NodesStats] -> ShowS # | |
Eq NodesStats Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: NodesStats -> NodesStats -> Bool # (/=) :: NodesStats -> NodesStats -> Bool # |
newtype PluginName Source #
Instances
FromJSON PluginName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser PluginName # parseJSONList :: Value -> Parser [PluginName] # | |
Show PluginName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> PluginName -> ShowS # show :: PluginName -> String # showList :: [PluginName] -> ShowS # | |
Eq PluginName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: PluginName -> PluginName -> Bool # (/=) :: PluginName -> PluginName -> Bool # | |
Ord PluginName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes compare :: PluginName -> PluginName -> Ordering # (<) :: PluginName -> PluginName -> Bool # (<=) :: PluginName -> PluginName -> Bool # (>) :: PluginName -> PluginName -> Bool # (>=) :: PluginName -> PluginName -> Bool # max :: PluginName -> PluginName -> PluginName # min :: PluginName -> PluginName -> PluginName # |
data ShardResult Source #
ShardResult | |
|
Instances
FromJSON ShardResult Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser ShardResult # parseJSONList :: Value -> Parser [ShardResult] # | |
ToJSON ShardResult Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes toJSON :: ShardResult -> Value # toEncoding :: ShardResult -> Encoding # toJSONList :: [ShardResult] -> Value # toEncodingList :: [ShardResult] -> Encoding # omitField :: ShardResult -> Bool # | |
Show ShardResult Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> ShardResult -> ShowS # show :: ShardResult -> String # showList :: [ShardResult] -> ShowS # | |
Eq ShardResult Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: ShardResult -> ShardResult -> Bool # (/=) :: ShardResult -> ShardResult -> Bool # |
newtype ShardsResult Source #
Instances
FromJSON ShardsResult Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes parseJSON :: Value -> Parser ShardsResult # parseJSONList :: Value -> Parser [ShardsResult] # | |
Show ShardsResult Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> ShardsResult -> ShowS # show :: ShardsResult -> String # showList :: [ShardsResult] -> ShowS # | |
Eq ShardsResult Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: ShardsResult -> ShardsResult -> Bool # (/=) :: ShardsResult -> ShardsResult -> Bool # |
data ThreadPool Source #
Instances
Show ThreadPool Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> ThreadPool -> ShowS # show :: ThreadPool -> String # showList :: [ThreadPool] -> ShowS # | |
Eq ThreadPool Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: ThreadPool -> ThreadPool -> Bool # (/=) :: ThreadPool -> ThreadPool -> Bool # |
data ThreadPoolSize Source #
Instances
FromJSON ThreadPoolSize Source # | |
Show ThreadPoolSize Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> ThreadPoolSize -> ShowS # show :: ThreadPoolSize -> String # showList :: [ThreadPoolSize] -> ShowS # | |
Eq ThreadPoolSize Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: ThreadPoolSize -> ThreadPoolSize -> Bool # (/=) :: ThreadPoolSize -> ThreadPoolSize -> Bool # |
data ThreadPoolType Source #
Instances
FromJSON ThreadPoolType Source # | |
Show ThreadPoolType Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes showsPrec :: Int -> ThreadPoolType -> ShowS # show :: ThreadPoolType -> String # showList :: [ThreadPoolType] -> ShowS # | |
Eq ThreadPoolType Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes (==) :: ThreadPoolType -> ThreadPoolType -> Bool # (/=) :: ThreadPoolType -> ThreadPoolType -> Bool # |
Version
is embedded in Status
Instances
FromJSON Version Source # | |
ToJSON Version Source # | |
Generic Version Source # | |
Show Version Source # | |
Eq Version Source # | |
type Rep Version Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Nodes type Rep Version = D1 ('MetaData "Version" "Database.Bloodhound.Internal.Versions.Common.Types.Nodes" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) (C1 ('MetaCons "Version" 'PrefixI 'True) ((S1 ('MetaSel ('Just "number") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionNumber) :*: S1 ('MetaSel ('Just "build_hash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildHash)) :*: (S1 ('MetaSel ('Just "build_date") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime) :*: (S1 ('MetaSel ('Just "build_snapshot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "lucene_version") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionNumber))))) |
newtype VersionNumber Source #
Traditional software versioning number
Instances
Optics
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.
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.
newtype RelationName Source #
RelationName
describes a relation role between parend and child Documents
in a Join relarionship: https://www.elastic.co/guide/en/elasticsearch/reference/current/parent-join.html
Instances
FromJSON RelationName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser RelationName # parseJSONList :: Value -> Parser [RelationName] # | |
ToJSON RelationName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: RelationName -> Value # toEncoding :: RelationName -> Encoding # toJSONList :: [RelationName] -> Value # toEncodingList :: [RelationName] -> Encoding # omitField :: RelationName -> Bool # | |
Read RelationName Source # | |
Show RelationName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> RelationName -> ShowS # show :: RelationName -> String # showList :: [RelationName] -> ShowS # | |
Eq RelationName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: RelationName -> RelationName -> Bool # (/=) :: RelationName -> RelationName -> Bool # |
newtype QueryString Source #
QueryString
is used to wrap query text bodies, be they human written or not.
Instances
FromJSON QueryString Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser QueryString # parseJSONList :: Value -> Parser [QueryString] # | |
ToJSON QueryString Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: QueryString -> Value # toEncoding :: QueryString -> Encoding # toJSONList :: [QueryString] -> Value # toEncodingList :: [QueryString] -> Encoding # omitField :: QueryString -> Bool # | |
Show QueryString Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> QueryString -> ShowS # show :: QueryString -> String # showList :: [QueryString] -> ShowS # | |
Eq QueryString Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: QueryString -> QueryString -> Bool # (/=) :: QueryString -> QueryString -> Bool # |
CacheKey
is used in RegexpFilter
to key regex caching.
newtype CutoffFrequency Source #
Instances
FromJSON CutoffFrequency Source # | |
ToJSON CutoffFrequency Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: CutoffFrequency -> Value # toEncoding :: CutoffFrequency -> Encoding # toJSONList :: [CutoffFrequency] -> Value # toEncodingList :: [CutoffFrequency] -> Encoding # omitField :: CutoffFrequency -> Bool # | |
Show CutoffFrequency Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> CutoffFrequency -> ShowS # show :: CutoffFrequency -> String # showList :: [CutoffFrequency] -> ShowS # | |
Eq CutoffFrequency Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: CutoffFrequency -> CutoffFrequency -> Bool # (/=) :: CutoffFrequency -> CutoffFrequency -> Bool # |
newtype MaxExpansions Source #
Instances
FromJSON MaxExpansions Source # | |
ToJSON MaxExpansions Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: MaxExpansions -> Value # toEncoding :: MaxExpansions -> Encoding # toJSONList :: [MaxExpansions] -> Value # toEncodingList :: [MaxExpansions] -> Encoding # omitField :: MaxExpansions -> Bool # | |
Show MaxExpansions Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> MaxExpansions -> ShowS # show :: MaxExpansions -> String # showList :: [MaxExpansions] -> ShowS # | |
Eq MaxExpansions Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: MaxExpansions -> MaxExpansions -> Bool # (/=) :: MaxExpansions -> MaxExpansions -> Bool # |
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 Tiebreaker Source #
Instances
FromJSON Tiebreaker Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser Tiebreaker # parseJSONList :: Value -> Parser [Tiebreaker] # | |
ToJSON Tiebreaker Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: Tiebreaker -> Value # toEncoding :: Tiebreaker -> Encoding # toJSONList :: [Tiebreaker] -> Value # toEncodingList :: [Tiebreaker] -> Encoding # omitField :: Tiebreaker -> Bool # | |
Show Tiebreaker Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> Tiebreaker -> ShowS # show :: Tiebreaker -> String # showList :: [Tiebreaker] -> ShowS # | |
Eq Tiebreaker Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: Tiebreaker -> Tiebreaker -> Bool # (/=) :: Tiebreaker -> Tiebreaker -> 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.
Instances
FromJSON MinimumMatch Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser MinimumMatch # parseJSONList :: Value -> Parser [MinimumMatch] # | |
ToJSON MinimumMatch Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: MinimumMatch -> Value # toEncoding :: MinimumMatch -> Encoding # toJSONList :: [MinimumMatch] -> Value # toEncodingList :: [MinimumMatch] -> Encoding # omitField :: MinimumMatch -> Bool # | |
Show MinimumMatch Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> MinimumMatch -> ShowS # show :: MinimumMatch -> String # showList :: [MinimumMatch] -> ShowS # | |
Eq MinimumMatch Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: MinimumMatch -> MinimumMatch -> Bool # (/=) :: MinimumMatch -> MinimumMatch -> Bool # |
newtype DisableCoord Source #
Instances
FromJSON DisableCoord Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser DisableCoord # parseJSONList :: Value -> Parser [DisableCoord] # | |
ToJSON DisableCoord Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: DisableCoord -> Value # toEncoding :: DisableCoord -> Encoding # toJSONList :: [DisableCoord] -> Value # toEncodingList :: [DisableCoord] -> Encoding # omitField :: DisableCoord -> Bool # | |
Show DisableCoord Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> DisableCoord -> ShowS # show :: DisableCoord -> String # showList :: [DisableCoord] -> ShowS # | |
Eq DisableCoord Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: DisableCoord -> DisableCoord -> Bool # (/=) :: DisableCoord -> DisableCoord -> Bool # |
newtype IgnoreTermFrequency Source #
Instances
newtype MinimumTermFrequency Source #
Instances
newtype MaxQueryTerms Source #
Instances
FromJSON MaxQueryTerms Source # | |
ToJSON MaxQueryTerms Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: MaxQueryTerms -> Value # toEncoding :: MaxQueryTerms -> Encoding # toJSONList :: [MaxQueryTerms] -> Value # toEncodingList :: [MaxQueryTerms] -> Encoding # omitField :: MaxQueryTerms -> Bool # | |
Show MaxQueryTerms Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> MaxQueryTerms -> ShowS # show :: MaxQueryTerms -> String # showList :: [MaxQueryTerms] -> ShowS # | |
Eq MaxQueryTerms Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: MaxQueryTerms -> MaxQueryTerms -> Bool # (/=) :: MaxQueryTerms -> MaxQueryTerms -> Bool # |
newtype PrefixLength Source #
PrefixLength
is the prefix length used in queries, defaults to 0.
Instances
FromJSON PrefixLength Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser PrefixLength # parseJSONList :: Value -> Parser [PrefixLength] # | |
ToJSON PrefixLength Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: PrefixLength -> Value # toEncoding :: PrefixLength -> Encoding # toJSONList :: [PrefixLength] -> Value # toEncodingList :: [PrefixLength] -> Encoding # omitField :: PrefixLength -> Bool # | |
Show PrefixLength Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> PrefixLength -> ShowS # show :: PrefixLength -> String # showList :: [PrefixLength] -> ShowS # | |
Eq PrefixLength Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: PrefixLength -> PrefixLength -> Bool # (/=) :: PrefixLength -> PrefixLength -> Bool # |
newtype PercentMatch Source #
Instances
FromJSON PercentMatch Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser PercentMatch # parseJSONList :: Value -> Parser [PercentMatch] # | |
ToJSON PercentMatch Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: PercentMatch -> Value # toEncoding :: PercentMatch -> Encoding # toJSONList :: [PercentMatch] -> Value # toEncodingList :: [PercentMatch] -> Encoding # omitField :: PercentMatch -> Bool # | |
Show PercentMatch Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> PercentMatch -> ShowS # show :: PercentMatch -> String # showList :: [PercentMatch] -> ShowS # | |
Eq PercentMatch Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: PercentMatch -> PercentMatch -> Bool # (/=) :: PercentMatch -> PercentMatch -> Bool # |
newtype AllowLeadingWildcard Source #
Allowing a wildcard at the beginning of a word (eg "*ing") is particularly
heavy, because all terms in the index need to be examined, just in case
they match. Leading wildcards can be disabled by setting
AllowLeadingWildcard
to false.
Instances
newtype LowercaseExpanded Source #
Instances
FromJSON LowercaseExpanded Source # | |
ToJSON LowercaseExpanded Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: LowercaseExpanded -> Value # toEncoding :: LowercaseExpanded -> Encoding # toJSONList :: [LowercaseExpanded] -> Value # toEncodingList :: [LowercaseExpanded] -> Encoding # omitField :: LowercaseExpanded -> Bool # | |
Show LowercaseExpanded Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> LowercaseExpanded -> ShowS # show :: LowercaseExpanded -> String # showList :: [LowercaseExpanded] -> ShowS # | |
Eq LowercaseExpanded Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: LowercaseExpanded -> LowercaseExpanded -> Bool # (/=) :: LowercaseExpanded -> LowercaseExpanded -> Bool # |
newtype EnablePositionIncrements Source #
Instances
newtype AnalyzeWildcard Source #
By default, wildcard terms in a query are not analyzed.
Setting AnalyzeWildcard
to true enables best-effort analysis.
Instances
FromJSON AnalyzeWildcard Source # | |
ToJSON AnalyzeWildcard Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: AnalyzeWildcard -> Value # toEncoding :: AnalyzeWildcard -> Encoding # toJSONList :: [AnalyzeWildcard] -> Value # toEncodingList :: [AnalyzeWildcard] -> Encoding # omitField :: AnalyzeWildcard -> Bool # | |
Show AnalyzeWildcard Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> AnalyzeWildcard -> ShowS # show :: AnalyzeWildcard -> String # showList :: [AnalyzeWildcard] -> ShowS # | |
Eq AnalyzeWildcard Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: AnalyzeWildcard -> AnalyzeWildcard -> Bool # (/=) :: AnalyzeWildcard -> AnalyzeWildcard -> Bool # |
newtype GeneratePhraseQueries Source #
GeneratePhraseQueries
defaults to false.
Instances
Locale
is used for string conversions - defaults to ROOT.
newtype MaxWordLength Source #
Instances
FromJSON MaxWordLength Source # | |
ToJSON MaxWordLength Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: MaxWordLength -> Value # toEncoding :: MaxWordLength -> Encoding # toJSONList :: [MaxWordLength] -> Value # toEncodingList :: [MaxWordLength] -> Encoding # omitField :: MaxWordLength -> Bool # | |
Show MaxWordLength Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> MaxWordLength -> ShowS # show :: MaxWordLength -> String # showList :: [MaxWordLength] -> ShowS # | |
Eq MaxWordLength Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: MaxWordLength -> MaxWordLength -> Bool # (/=) :: MaxWordLength -> MaxWordLength -> Bool # |
newtype MinWordLength Source #
Instances
FromJSON MinWordLength Source # | |
ToJSON MinWordLength Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: MinWordLength -> Value # toEncoding :: MinWordLength -> Encoding # toJSONList :: [MinWordLength] -> Value # toEncodingList :: [MinWordLength] -> Encoding # omitField :: MinWordLength -> Bool # | |
Show MinWordLength Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> MinWordLength -> ShowS # show :: MinWordLength -> String # showList :: [MinWordLength] -> ShowS # | |
Eq MinWordLength Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: MinWordLength -> MinWordLength -> Bool # (/=) :: MinWordLength -> MinWordLength -> Bool # |
newtype PhraseSlop Source #
PhraseSlop
sets the default slop for phrases, 0 means exact
phrase matches. Default is 0.
Instances
FromJSON PhraseSlop Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser PhraseSlop # parseJSONList :: Value -> Parser [PhraseSlop] # | |
ToJSON PhraseSlop Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: PhraseSlop -> Value # toEncoding :: PhraseSlop -> Encoding # toJSONList :: [PhraseSlop] -> Value # toEncodingList :: [PhraseSlop] -> Encoding # omitField :: PhraseSlop -> Bool # | |
Show PhraseSlop Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> PhraseSlop -> ShowS # show :: PhraseSlop -> String # showList :: [PhraseSlop] -> ShowS # | |
Eq PhraseSlop Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: PhraseSlop -> PhraseSlop -> Bool # (/=) :: PhraseSlop -> PhraseSlop -> Bool # |
newtype MinDocFrequency Source #
Instances
FromJSON MinDocFrequency Source # | |
ToJSON MinDocFrequency Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: MinDocFrequency -> Value # toEncoding :: MinDocFrequency -> Encoding # toJSONList :: [MinDocFrequency] -> Value # toEncodingList :: [MinDocFrequency] -> Encoding # omitField :: MinDocFrequency -> Bool # | |
Show MinDocFrequency Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> MinDocFrequency -> ShowS # show :: MinDocFrequency -> String # showList :: [MinDocFrequency] -> ShowS # | |
Eq MinDocFrequency Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: MinDocFrequency -> MinDocFrequency -> Bool # (/=) :: MinDocFrequency -> MinDocFrequency -> Bool # |
newtype MaxDocFrequency Source #
Instances
FromJSON MaxDocFrequency Source # | |
ToJSON MaxDocFrequency Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: MaxDocFrequency -> Value # toEncoding :: MaxDocFrequency -> Encoding # toJSONList :: [MaxDocFrequency] -> Value # toEncodingList :: [MaxDocFrequency] -> Encoding # omitField :: MaxDocFrequency -> Bool # | |
Show MaxDocFrequency Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> MaxDocFrequency -> ShowS # show :: MaxDocFrequency -> String # showList :: [MaxDocFrequency] -> ShowS # | |
Eq MaxDocFrequency Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: MaxDocFrequency -> MaxDocFrequency -> Bool # (/=) :: MaxDocFrequency -> MaxDocFrequency -> Bool # |
newtype AggregateParentScore Source #
Indicates whether the relevance score of a matching parent document is aggregated into its child documents.
Instances
newtype IgnoreUnmapped Source #
Indicates whether to ignore an unmapped parent_type and not return any documents instead of an error.
Instances
FromJSON IgnoreUnmapped Source # | |
ToJSON IgnoreUnmapped Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: IgnoreUnmapped -> Value # toEncoding :: IgnoreUnmapped -> Encoding # toJSONList :: [IgnoreUnmapped] -> Value # toEncodingList :: [IgnoreUnmapped] -> Encoding # omitField :: IgnoreUnmapped -> Bool # | |
Show IgnoreUnmapped Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> IgnoreUnmapped -> ShowS # show :: IgnoreUnmapped -> String # showList :: [IgnoreUnmapped] -> ShowS # | |
Eq IgnoreUnmapped Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: IgnoreUnmapped -> IgnoreUnmapped -> Bool # (/=) :: IgnoreUnmapped -> 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.
Instances
FromJSON MinChildren Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser MinChildren # parseJSONList :: Value -> Parser [MinChildren] # | |
ToJSON MinChildren Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: MinChildren -> Value # toEncoding :: MinChildren -> Encoding # toJSONList :: [MinChildren] -> Value # toEncodingList :: [MinChildren] -> Encoding # omitField :: MinChildren -> Bool # | |
Show MinChildren Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> MinChildren -> ShowS # show :: MinChildren -> String # showList :: [MinChildren] -> ShowS # | |
Eq MinChildren Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: MinChildren -> MinChildren -> Bool # (/=) :: MinChildren -> MinChildren -> Bool # |
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.
Instances
FromJSON MaxChildren Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser MaxChildren # parseJSONList :: Value -> Parser [MaxChildren] # | |
ToJSON MaxChildren Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: MaxChildren -> Value # toEncoding :: MaxChildren -> Encoding # toJSONList :: [MaxChildren] -> Value # toEncodingList :: [MaxChildren] -> Encoding # omitField :: MaxChildren -> Bool # | |
Show MaxChildren Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> MaxChildren -> ShowS # show :: MaxChildren -> String # showList :: [MaxChildren] -> ShowS # | |
Eq MaxChildren Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: MaxChildren -> MaxChildren -> Bool # (/=) :: MaxChildren -> MaxChildren -> Bool # |
Newtype wrapper to parse ES's concerning tendency to in some APIs return a floating point number of milliseconds since epoch ಠ_ಠ
newtype BoostTerms Source #
Instances
FromJSON BoostTerms Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser BoostTerms # parseJSONList :: Value -> Parser [BoostTerms] # | |
ToJSON BoostTerms Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: BoostTerms -> Value # toEncoding :: BoostTerms -> Encoding # toJSONList :: [BoostTerms] -> Value # toEncodingList :: [BoostTerms] -> Encoding # omitField :: BoostTerms -> Bool # | |
Show BoostTerms Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> BoostTerms -> ShowS # show :: BoostTerms -> String # showList :: [BoostTerms] -> ShowS # | |
Eq BoostTerms Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: BoostTerms -> BoostTerms -> Bool # (/=) :: BoostTerms -> BoostTerms -> Bool # |
newtype ReplicaCount Source #
ReplicaCount
is part of IndexSettings
Instances
FromJSON ReplicaCount Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser ReplicaCount # parseJSONList :: Value -> Parser [ReplicaCount] # | |
ToJSON ReplicaCount Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: ReplicaCount -> Value # toEncoding :: ReplicaCount -> Encoding # toJSONList :: [ReplicaCount] -> Value # toEncodingList :: [ReplicaCount] -> Encoding # omitField :: ReplicaCount -> Bool # | |
Show ReplicaCount Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> ReplicaCount -> ShowS # show :: ReplicaCount -> String # showList :: [ReplicaCount] -> ShowS # | |
Eq ReplicaCount Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: ReplicaCount -> ReplicaCount -> Bool # (/=) :: ReplicaCount -> ReplicaCount -> Bool # |
newtype ShardCount Source #
ShardCount
is part of IndexSettings
Instances
FromJSON ShardCount Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser ShardCount # parseJSONList :: Value -> Parser [ShardCount] # | |
ToJSON ShardCount Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: ShardCount -> Value # toEncoding :: ShardCount -> Encoding # toJSONList :: [ShardCount] -> Value # toEncodingList :: [ShardCount] -> Encoding # omitField :: ShardCount -> Bool # | |
Show ShardCount Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> ShardCount -> ShowS # show :: ShardCount -> String # showList :: [ShardCount] -> ShowS # | |
Eq ShardCount Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: ShardCount -> ShardCount -> Bool # (/=) :: ShardCount -> ShardCount -> Bool # |
IndexName
is used to describe which index to querycreatedelete
Instances
FromJSON IndexName Source # | |
FromJSONKey IndexName Source # | |
ToJSON IndexName Source # | |
ToJSONKey IndexName Source # | |
Semigroup IndexName Source # | |
Generic IndexName Source # | |
Show IndexName Source # | |
Eq IndexName Source # | |
Ord IndexName Source # | |
Hashable IndexName Source # | |
type Rep IndexName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes type Rep IndexName = D1 ('MetaData "IndexName" "Database.Bloodhound.Internal.Versions.Common.Types.Newtypes" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'True) (C1 ('MetaCons "IndexName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
unIndexName :: IndexName -> Text Source #
newtype IndexAliasName Source #
Instances
ToJSON IndexAliasName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: IndexAliasName -> Value # toEncoding :: IndexAliasName -> Encoding # toJSONList :: [IndexAliasName] -> Value # toEncodingList :: [IndexAliasName] -> Encoding # omitField :: IndexAliasName -> Bool # | |
Show IndexAliasName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> IndexAliasName -> ShowS # show :: IndexAliasName -> String # showList :: [IndexAliasName] -> ShowS # | |
Eq IndexAliasName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: IndexAliasName -> IndexAliasName -> Bool # (/=) :: IndexAliasName -> IndexAliasName -> Bool # |
Instances
Applicative MaybeNA Source # | |
Functor MaybeNA Source # | |
Monad MaybeNA Source # | |
FromJSON a => FromJSON (MaybeNA a) Source # | |
Show a => Show (MaybeNA a) Source # | |
Eq a => Eq (MaybeNA a) Source # | |
newtype SnapshotName Source #
Instances
FromJSON SnapshotName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser SnapshotName # parseJSONList :: Value -> Parser [SnapshotName] # | |
ToJSON SnapshotName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: SnapshotName -> Value # toEncoding :: SnapshotName -> Encoding # toJSONList :: [SnapshotName] -> Value # toEncodingList :: [SnapshotName] -> Encoding # omitField :: SnapshotName -> Bool # | |
Show SnapshotName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> SnapshotName -> ShowS # show :: SnapshotName -> String # showList :: [SnapshotName] -> ShowS # | |
Eq SnapshotName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: SnapshotName -> SnapshotName -> Bool # (/=) :: SnapshotName -> SnapshotName -> Bool # |
Milliseconds
unMS :: MS -> NominalDiffTime Source #
newtype TokenFilter Source #
Instances
FromJSON TokenFilter Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser TokenFilter # parseJSONList :: Value -> Parser [TokenFilter] # | |
ToJSON TokenFilter Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: TokenFilter -> Value # toEncoding :: TokenFilter -> Encoding # toJSONList :: [TokenFilter] -> Value # toEncodingList :: [TokenFilter] -> Encoding # omitField :: TokenFilter -> Bool # | |
Show TokenFilter Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> TokenFilter -> ShowS # show :: TokenFilter -> String # showList :: [TokenFilter] -> ShowS # | |
Eq TokenFilter Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: TokenFilter -> TokenFilter -> Bool # (/=) :: TokenFilter -> TokenFilter -> Bool # |
newtype CharFilter Source #
Instances
FromJSON CharFilter Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes parseJSON :: Value -> Parser CharFilter # parseJSONList :: Value -> Parser [CharFilter] # | |
ToJSON CharFilter Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes toJSON :: CharFilter -> Value # toEncoding :: CharFilter -> Encoding # toJSONList :: [CharFilter] -> Value # toEncodingList :: [CharFilter] -> Encoding # omitField :: CharFilter -> Bool # | |
Show CharFilter Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes showsPrec :: Int -> CharFilter -> ShowS # show :: CharFilter -> String # showList :: [CharFilter] -> ShowS # | |
Eq CharFilter Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Newtypes (==) :: CharFilter -> CharFilter -> Bool # (/=) :: CharFilter -> CharFilter -> Bool # |
data AliasRouting Source #
AllAliasRouting RoutingValue | |
GranularAliasRouting (Maybe SearchAliasRouting) (Maybe IndexAliasRouting) |
Instances
FromJSON AliasRouting Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices parseJSON :: Value -> Parser AliasRouting # parseJSONList :: Value -> Parser [AliasRouting] # | |
ToJSON AliasRouting Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices toJSON :: AliasRouting -> Value # toEncoding :: AliasRouting -> Encoding # toJSONList :: [AliasRouting] -> Value # toEncodingList :: [AliasRouting] -> Encoding # omitField :: AliasRouting -> Bool # | |
Show AliasRouting Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> AliasRouting -> ShowS # show :: AliasRouting -> String # showList :: [AliasRouting] -> ShowS # | |
Eq AliasRouting Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: AliasRouting -> AliasRouting -> Bool # (/=) :: AliasRouting -> AliasRouting -> Bool # |
data AllocationPolicy Source #
AllocAll | Allows shard allocation for all shards. |
AllocPrimaries | Allows shard allocation only for primary shards. |
AllocNewPrimaries | Allows shard allocation only for primary shards for new indices. |
AllocNone | No shard allocation is allowed |
Instances
data CompoundFormat Source #
CompoundFileFormat Bool | |
MergeSegmentVsTotalIndex Double | percentage between 0 and 1 where 0 is false, 1 is true |
Instances
data Compression Source #
CompressionDefault | Compress with LZ4 |
CompressionBest | Compress with DEFLATE. Elastic blogs that this can reduce disk use by 15%-25%. |
Instances
newtype FieldDefinition Source #
Instances
Show FieldDefinition Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> FieldDefinition -> ShowS # show :: FieldDefinition -> String # showList :: [FieldDefinition] -> ShowS # | |
Eq FieldDefinition Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: FieldDefinition -> FieldDefinition -> Bool # (/=) :: FieldDefinition -> FieldDefinition -> Bool # |
data ForceMergeIndexSettings Source #
ForceMergeIndexSettings
is used to configure index optimization. See
https://www.elastic.co/guide/en/elasticsearch/reference/current/indices-forcemerge.html
for more info.
ForceMergeIndexSettings | |
|
Instances
data IndexAlias Source #
Instances
ToJSON IndexAlias Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices toJSON :: IndexAlias -> Value # toEncoding :: IndexAlias -> Encoding # toJSONList :: [IndexAlias] -> Value # toEncodingList :: [IndexAlias] -> Encoding # omitField :: IndexAlias -> Bool # | |
Show IndexAlias Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> IndexAlias -> ShowS # show :: IndexAlias -> String # showList :: [IndexAlias] -> ShowS # | |
Eq IndexAlias Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: IndexAlias -> IndexAlias -> Bool # (/=) :: IndexAlias -> IndexAlias -> Bool # |
data IndexAliasAction Source #
Instances
ToJSON IndexAliasAction Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices toJSON :: IndexAliasAction -> Value # toEncoding :: IndexAliasAction -> Encoding # toJSONList :: [IndexAliasAction] -> Value # toEncodingList :: [IndexAliasAction] -> Encoding # omitField :: IndexAliasAction -> Bool # | |
Show IndexAliasAction Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> IndexAliasAction -> ShowS # show :: IndexAliasAction -> String # showList :: [IndexAliasAction] -> ShowS # | |
Eq IndexAliasAction Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: IndexAliasAction -> IndexAliasAction -> Bool # (/=) :: IndexAliasAction -> IndexAliasAction -> Bool # |
data IndexAliasCreate Source #
Instances
FromJSON IndexAliasCreate Source # | |
ToJSON IndexAliasCreate Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices toJSON :: IndexAliasCreate -> Value # toEncoding :: IndexAliasCreate -> Encoding # toJSONList :: [IndexAliasCreate] -> Value # toEncodingList :: [IndexAliasCreate] -> Encoding # omitField :: IndexAliasCreate -> Bool # | |
Show IndexAliasCreate Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> IndexAliasCreate -> ShowS # show :: IndexAliasCreate -> String # showList :: [IndexAliasCreate] -> ShowS # | |
Eq IndexAliasCreate Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: IndexAliasCreate -> IndexAliasCreate -> Bool # (/=) :: IndexAliasCreate -> IndexAliasCreate -> Bool # |
newtype IndexAliasRouting Source #
Instances
FromJSON IndexAliasRouting Source # | |
ToJSON IndexAliasRouting Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices toJSON :: IndexAliasRouting -> Value # toEncoding :: IndexAliasRouting -> Encoding # toJSONList :: [IndexAliasRouting] -> Value # toEncodingList :: [IndexAliasRouting] -> Encoding # omitField :: IndexAliasRouting -> Bool # | |
Show IndexAliasRouting Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> IndexAliasRouting -> ShowS # show :: IndexAliasRouting -> String # showList :: [IndexAliasRouting] -> ShowS # | |
Eq IndexAliasRouting Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: IndexAliasRouting -> IndexAliasRouting -> Bool # (/=) :: IndexAliasRouting -> IndexAliasRouting -> Bool # |
data IndexAliasSummary Source #
IndexAliasSummary
is a summary of an index alias configured for a server.
Instances
Show IndexAliasSummary Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> IndexAliasSummary -> ShowS # show :: IndexAliasSummary -> String # showList :: [IndexAliasSummary] -> ShowS # | |
Eq IndexAliasSummary Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: IndexAliasSummary -> IndexAliasSummary -> Bool # (/=) :: IndexAliasSummary -> IndexAliasSummary -> Bool # |
newtype IndexAliasesSummary Source #
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
Instances
data IndexMappingsLimits Source #
'IndexMappingsLimits is used to configure index's limits. https://www.elastic.co/guide/en/elasticsearch/reference/master/mapping-settings-limit.html
Instances
newtype IndexPattern Source #
IndexPattern
represents a pattern which is matched against index names
Instances
FromJSON IndexPattern Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices parseJSON :: Value -> Parser IndexPattern # parseJSONList :: Value -> Parser [IndexPattern] # | |
ToJSON IndexPattern Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices toJSON :: IndexPattern -> Value # toEncoding :: IndexPattern -> Encoding # toJSONList :: [IndexPattern] -> Value # toEncodingList :: [IndexPattern] -> Encoding # omitField :: IndexPattern -> Bool # | |
Show IndexPattern Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> IndexPattern -> ShowS # show :: IndexPattern -> String # showList :: [IndexPattern] -> ShowS # | |
Eq IndexPattern Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: IndexPattern -> IndexPattern -> Bool # (/=) :: IndexPattern -> IndexPattern -> Bool # |
data IndexSelection Source #
IndexSelection
is used for APIs which take a single index, a list of
indexes, or the special _all
index.
Instances
Show IndexSelection Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> IndexSelection -> ShowS # show :: IndexSelection -> String # showList :: [IndexSelection] -> ShowS # | |
Eq IndexSelection Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: IndexSelection -> IndexSelection -> Bool # (/=) :: IndexSelection -> IndexSelection -> Bool # |
data IndexSettings Source #
IndexSettings
is used to configure the shards and replicas when
you create an Elasticsearch Index.
http://www.elastic.co/guide/en/elasticsearch/reference/current/indices-create-index.html
Instances
data IndexSettingsSummary Source #
Instances
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
Instances
ToJSON IndexTemplate Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices toJSON :: IndexTemplate -> Value # toEncoding :: IndexTemplate -> Encoding # toJSONList :: [IndexTemplate] -> Value # toEncodingList :: [IndexTemplate] -> Encoding # omitField :: IndexTemplate -> Bool # |
data JoinRelation Source #
Instances
Show JoinRelation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> JoinRelation -> ShowS # show :: JoinRelation -> String # showList :: [JoinRelation] -> ShowS # | |
Eq JoinRelation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: JoinRelation -> JoinRelation -> Bool # (/=) :: JoinRelation -> JoinRelation -> Bool # |
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.
data MappingField Source #
Instances
Show MappingField Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> MappingField -> ShowS # show :: MappingField -> String # showList :: [MappingField] -> ShowS # | |
Eq MappingField Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: MappingField -> MappingField -> Bool # (/=) :: MappingField -> MappingField -> Bool # |
newtype NominalDiffTimeJSON Source #
Instances
data OpenCloseIndex Source #
OpenCloseIndex
is a sum type for opening and closing indices.
http://www.elastic.co/guide/en/elasticsearch/reference/current/indices-open-close.html
Instances
Show OpenCloseIndex Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> OpenCloseIndex -> ShowS # show :: OpenCloseIndex -> String # showList :: [OpenCloseIndex] -> ShowS # | |
Eq OpenCloseIndex Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: OpenCloseIndex -> OpenCloseIndex -> Bool # (/=) :: OpenCloseIndex -> OpenCloseIndex -> Bool # |
data ReplicaBounds Source #
Instances
FromJSON ReplicaBounds Source # | |
ToJSON ReplicaBounds Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices toJSON :: ReplicaBounds -> Value # toEncoding :: ReplicaBounds -> Encoding # toJSONList :: [ReplicaBounds] -> Value # toEncodingList :: [ReplicaBounds] -> Encoding # omitField :: ReplicaBounds -> Bool # | |
Show ReplicaBounds Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> ReplicaBounds -> ShowS # show :: ReplicaBounds -> String # showList :: [ReplicaBounds] -> ShowS # | |
Eq ReplicaBounds Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: ReplicaBounds -> ReplicaBounds -> Bool # (/=) :: ReplicaBounds -> ReplicaBounds -> Bool # |
newtype RoutingValue Source #
Instances
FromJSON RoutingValue Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices parseJSON :: Value -> Parser RoutingValue # parseJSONList :: Value -> Parser [RoutingValue] # | |
ToJSON RoutingValue Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices toJSON :: RoutingValue -> Value # toEncoding :: RoutingValue -> Encoding # toJSONList :: [RoutingValue] -> Value # toEncodingList :: [RoutingValue] -> Encoding # omitField :: RoutingValue -> Bool # | |
Show RoutingValue Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> RoutingValue -> ShowS # show :: RoutingValue -> String # showList :: [RoutingValue] -> ShowS # | |
Eq RoutingValue Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: RoutingValue -> RoutingValue -> Bool # (/=) :: RoutingValue -> RoutingValue -> Bool # |
newtype SearchAliasRouting Source #
Instances
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.elastic.co/guide/en/elasticsearch/reference/current/indices-status.html#indices-status
newtype TemplateName Source #
TemplateName
is used to describe which template to querycreatedelete
Instances
FromJSON TemplateName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices parseJSON :: Value -> Parser TemplateName # parseJSONList :: Value -> Parser [TemplateName] # | |
ToJSON TemplateName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices toJSON :: TemplateName -> Value # toEncoding :: TemplateName -> Encoding # toJSONList :: [TemplateName] -> Value # toEncodingList :: [TemplateName] -> Encoding # omitField :: TemplateName -> Bool # | |
Show TemplateName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices showsPrec :: Int -> TemplateName -> ShowS # show :: TemplateName -> String # showList :: [TemplateName] -> ShowS # | |
Eq TemplateName Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Indices (==) :: TemplateName -> TemplateName -> Bool # (/=) :: TemplateName -> TemplateName -> Bool # |
data UpdatableIndexSetting Source #
UpdatableIndexSetting
are settings which may be updated after an index is created.
https://www.elastic.co/guide/en/elasticsearch/reference/current/indices-update-settings.html
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 |
Instances
defaultForceMergeIndexSettings :: ForceMergeIndexSettings Source #
defaultForceMergeIndexSettings
implements the default settings that
Elasticsearch uses for index optimization. maxNumSegments
is Nothing,
onlyExpungeDeletes
is False, and flushAfterOptimize is True.
defaultIndexDocumentSettings :: IndexDocumentSettings Source #
Reasonable default settings. Chooses no version control and no parent.
defaultIndexSettings :: IndexSettings Source #
defaultIndexSettings
is an IndexSettings
with 3 shards and
2 replicas.
Optics
data Highlights Source #
Instances
ToJSON Highlights Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight toJSON :: Highlights -> Value # toEncoding :: Highlights -> Encoding # toJSONList :: [Highlights] -> Value # toEncodingList :: [Highlights] -> Encoding # omitField :: Highlights -> Bool # | |
Show Highlights Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight showsPrec :: Int -> Highlights -> ShowS # show :: Highlights -> String # showList :: [Highlights] -> ShowS # | |
Eq Highlights Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight (==) :: Highlights -> Highlights -> Bool # (/=) :: Highlights -> Highlights -> Bool # |
data FieldHighlight Source #
Instances
ToJSON FieldHighlight Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight toJSON :: FieldHighlight -> Value # toEncoding :: FieldHighlight -> Encoding # toJSONList :: [FieldHighlight] -> Value # toEncodingList :: [FieldHighlight] -> Encoding # omitField :: FieldHighlight -> Bool # | |
Show FieldHighlight Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight showsPrec :: Int -> FieldHighlight -> ShowS # show :: FieldHighlight -> String # showList :: [FieldHighlight] -> ShowS # | |
Eq FieldHighlight Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight (==) :: FieldHighlight -> FieldHighlight -> Bool # (/=) :: FieldHighlight -> FieldHighlight -> Bool # |
data HighlightSettings Source #
Instances
ToJSON HighlightSettings Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight toJSON :: HighlightSettings -> Value # toEncoding :: HighlightSettings -> Encoding # toJSONList :: [HighlightSettings] -> Value # toEncodingList :: [HighlightSettings] -> Encoding # omitField :: HighlightSettings -> Bool # | |
Show HighlightSettings Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight showsPrec :: Int -> HighlightSettings -> ShowS # show :: HighlightSettings -> String # showList :: [HighlightSettings] -> ShowS # | |
Eq HighlightSettings Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight (==) :: HighlightSettings -> HighlightSettings -> Bool # (/=) :: HighlightSettings -> HighlightSettings -> Bool # |
data PlainHighlight Source #
Instances
Show PlainHighlight Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight showsPrec :: Int -> PlainHighlight -> ShowS # show :: PlainHighlight -> String # showList :: [PlainHighlight] -> ShowS # | |
Eq PlainHighlight Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight (==) :: PlainHighlight -> PlainHighlight -> Bool # (/=) :: PlainHighlight -> PlainHighlight -> Bool # |
data PostingsHighlight Source #
Instances
Show PostingsHighlight Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight showsPrec :: Int -> PostingsHighlight -> ShowS # show :: PostingsHighlight -> String # showList :: [PostingsHighlight] -> ShowS # | |
Eq PostingsHighlight Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight (==) :: PostingsHighlight -> PostingsHighlight -> Bool # (/=) :: PostingsHighlight -> PostingsHighlight -> Bool # |
data FastVectorHighlight Source #
Instances
data CommonHighlight Source #
CommonHighlight | |
|
Instances
Show CommonHighlight Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight showsPrec :: Int -> CommonHighlight -> ShowS # show :: CommonHighlight -> String # showList :: [CommonHighlight] -> ShowS # | |
Eq CommonHighlight Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight (==) :: CommonHighlight -> CommonHighlight -> Bool # (/=) :: CommonHighlight -> CommonHighlight -> Bool # |
data NonPostings Source #
Instances
Show NonPostings Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight showsPrec :: Int -> NonPostings -> ShowS # show :: NonPostings -> String # showList :: [NonPostings] -> ShowS # | |
Eq NonPostings Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight (==) :: NonPostings -> NonPostings -> Bool # (/=) :: NonPostings -> NonPostings -> Bool # |
data HighlightEncoder Source #
Instances
ToJSON HighlightEncoder Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight toJSON :: HighlightEncoder -> Value # toEncoding :: HighlightEncoder -> Encoding # toJSONList :: [HighlightEncoder] -> Value # toEncodingList :: [HighlightEncoder] -> Encoding # omitField :: HighlightEncoder -> Bool # | |
Show HighlightEncoder Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight showsPrec :: Int -> HighlightEncoder -> ShowS # show :: HighlightEncoder -> String # showList :: [HighlightEncoder] -> ShowS # | |
Eq HighlightEncoder Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight (==) :: HighlightEncoder -> HighlightEncoder -> Bool # (/=) :: HighlightEncoder -> HighlightEncoder -> Bool # |
data HighlightTag Source #
TagSchema Text | |
CustomTags ([Text], [Text]) |
Instances
Show HighlightTag Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight showsPrec :: Int -> HighlightTag -> ShowS # show :: HighlightTag -> String # showList :: [HighlightTag] -> ShowS # | |
Eq HighlightTag Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Highlight (==) :: HighlightTag -> HighlightTag -> Bool # (/=) :: HighlightTag -> HighlightTag -> Bool # |
plainHighPairs :: Maybe PlainHighlight -> [Pair] Source #
postHighPairs :: Maybe PostingsHighlight -> [Pair] Source #
commonHighlightPairs :: Maybe CommonHighlight -> [Pair] Source #
nonPostingsToPairs :: Maybe NonPostings -> [Pair] Source #
highlightTagToPairs :: Maybe HighlightTag -> [Pair] Source #
newtype CountQuery Source #
Instances
ToJSON CountQuery Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Count toJSON :: CountQuery -> Value # toEncoding :: CountQuery -> Encoding # toJSONList :: [CountQuery] -> Value # toEncodingList :: [CountQuery] -> Encoding # omitField :: CountQuery -> Bool # | |
Show CountQuery Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Count showsPrec :: Int -> CountQuery -> ShowS # show :: CountQuery -> String # showList :: [CountQuery] -> ShowS # | |
Eq CountQuery Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Count (==) :: CountQuery -> CountQuery -> Bool # (/=) :: CountQuery -> CountQuery -> Bool # |
data CountResponse Source #
Instances
FromJSON CountResponse Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Count parseJSON :: Value -> Parser CountResponse # parseJSONList :: Value -> Parser [CountResponse] # | |
Show CountResponse Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Count showsPrec :: Int -> CountResponse -> ShowS # show :: CountResponse -> String # showList :: [CountResponse] -> ShowS # | |
Eq CountResponse Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Count (==) :: CountResponse -> CountResponse -> Bool # (/=) :: CountResponse -> CountResponse -> Bool # |
data CountShards Source #
Instances
FromJSON CountShards Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Count parseJSON :: Value -> Parser CountShards # parseJSONList :: Value -> Parser [CountShards] # | |
Show CountShards Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Count showsPrec :: Int -> CountShards -> ShowS # show :: CountShards -> String # showList :: [CountShards] -> ShowS # | |
Eq CountShards Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Count (==) :: CountShards -> CountShards -> Bool # (/=) :: CountShards -> CountShards -> Bool # |
Optics
Request
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.
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. |
Instances
Show BulkOperation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Bulk showsPrec :: Int -> BulkOperation -> ShowS # show :: BulkOperation -> String # showList :: [BulkOperation] -> ShowS # | |
Eq BulkOperation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Bulk (==) :: BulkOperation -> BulkOperation -> Bool # (/=) :: BulkOperation -> BulkOperation -> Bool # |
data UpsertActionMetadata Source #
Instances
data UpsertPayload Source #
Instances
Show UpsertPayload Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Bulk showsPrec :: Int -> UpsertPayload -> ShowS # show :: UpsertPayload -> String # showList :: [UpsertPayload] -> ShowS # | |
Eq UpsertPayload Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Bulk (==) :: UpsertPayload -> UpsertPayload -> Bool # (/=) :: UpsertPayload -> UpsertPayload -> Bool # |
Response
data BulkResponse Source #
BulkResponse | |
|
Instances
FromJSON BulkResponse Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Bulk parseJSON :: Value -> Parser BulkResponse # parseJSONList :: Value -> Parser [BulkResponse] # | |
Show BulkResponse Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Bulk showsPrec :: Int -> BulkResponse -> ShowS # show :: BulkResponse -> String # showList :: [BulkResponse] -> ShowS # | |
Eq BulkResponse Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Bulk (==) :: BulkResponse -> BulkResponse -> Bool # (/=) :: BulkResponse -> BulkResponse -> Bool # |
data BulkActionItem Source #
Instances
FromJSON BulkActionItem Source # | |
Show BulkActionItem Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Bulk showsPrec :: Int -> BulkActionItem -> ShowS # show :: BulkActionItem -> String # showList :: [BulkActionItem] -> ShowS # | |
Eq BulkActionItem Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Bulk (==) :: BulkActionItem -> BulkActionItem -> Bool # (/=) :: BulkActionItem -> BulkActionItem -> Bool # |
data BulkAction Source #
Instances
Show BulkAction Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Bulk showsPrec :: Int -> BulkAction -> ShowS # show :: BulkAction -> String # showList :: [BulkAction] -> ShowS # | |
Eq BulkAction Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Bulk (==) :: BulkAction -> BulkAction -> Bool # (/=) :: BulkAction -> BulkAction -> Bool # |
Optics
Instances
FromJSON Analysis Source # | |
ToJSON Analysis Source # | |
Generic Analysis Source # | |
Show Analysis Source # | |
Eq Analysis Source # | |
type Rep Analysis Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Analysis type Rep Analysis = D1 ('MetaData "Analysis" "Database.Bloodhound.Internal.Versions.Common.Types.Analysis" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) (C1 ('MetaCons "Analysis" 'PrefixI 'True) ((S1 ('MetaSel ('Just "analysisAnalyzer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text AnalyzerDefinition)) :*: S1 ('MetaSel ('Just "analysisTokenizer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text TokenizerDefinition))) :*: (S1 ('MetaSel ('Just "analysisTokenFilter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text TokenFilterDefinition)) :*: S1 ('MetaSel ('Just "analysisCharFilter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text CharFilterDefinition))))) |
data AnalyzerDefinition Source #
Instances
data CharFilterDefinition Source #
Character filters are used to preprocess the stream of characters before it is passed to the tokenizer.
Instances
data TokenizerDefinition Source #
Instances
Ngram | |
|
Instances
Generic Ngram Source # | |
Show Ngram Source # | |
Eq Ngram Source # | |
type Rep Ngram Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Analysis type Rep Ngram = D1 ('MetaData "Ngram" "Database.Bloodhound.Internal.Versions.Common.Types.Analysis" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) (C1 ('MetaCons "Ngram" 'PrefixI 'True) (S1 ('MetaSel ('Just "ngramMinGram") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "ngramMaxGram") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "ngramTokenChars") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TokenChar])))) |
Instances
FromJSON TokenChar Source # | |
ToJSON TokenChar Source # | |
Generic TokenChar Source # | |
Show TokenChar Source # | |
Eq TokenChar Source # | |
type Rep TokenChar Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Analysis type Rep TokenChar = D1 ('MetaData "TokenChar" "Database.Bloodhound.Internal.Versions.Common.Types.Analysis" "bloodhound-0.23.0.0-FmK0xPJsnw7U3vt3yN5OK" 'False) ((C1 ('MetaCons "TokenLetter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TokenDigit" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TokenWhitespace" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TokenPunctuation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TokenSymbol" 'PrefixI 'False) (U1 :: Type -> Type)))) |
data TokenFilterDefinition Source #
Token filters are used to create custom analyzers.
Instances
data NgramFilter Source #
Instances
ngramFilterToPairs :: NgramFilter -> [Pair] Source #
data EdgeNgramFilterSide Source #
Instances
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.
Instances
languageToText :: Language -> Text Source #
Instances
type Aggregations = Map Key Aggregation Source #
mkAggregations :: Key -> Aggregation -> Aggregations Source #
data Aggregation Source #
Instances
ToJSON Aggregation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation toJSON :: Aggregation -> Value # toEncoding :: Aggregation -> Encoding # toJSONList :: [Aggregation] -> Value # toEncodingList :: [Aggregation] -> Encoding # omitField :: Aggregation -> Bool # | |
Show Aggregation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> Aggregation -> ShowS # show :: Aggregation -> String # showList :: [Aggregation] -> ShowS # | |
Eq Aggregation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: Aggregation -> Aggregation -> Bool # (/=) :: Aggregation -> Aggregation -> Bool # |
data TopHitsAggregation Source #
Instances
Show TopHitsAggregation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> TopHitsAggregation -> ShowS # show :: TopHitsAggregation -> String # showList :: [TopHitsAggregation] -> ShowS # | |
Eq TopHitsAggregation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: TopHitsAggregation -> TopHitsAggregation -> Bool # (/=) :: TopHitsAggregation -> TopHitsAggregation -> Bool # |
data MissingAggregation Source #
Instances
Show MissingAggregation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> MissingAggregation -> ShowS # show :: MissingAggregation -> String # showList :: [MissingAggregation] -> ShowS # | |
Eq MissingAggregation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: MissingAggregation -> MissingAggregation -> Bool # (/=) :: MissingAggregation -> MissingAggregation -> Bool # |
data TermsAggregation Source #
Instances
Show TermsAggregation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> TermsAggregation -> ShowS # show :: TermsAggregation -> String # showList :: [TermsAggregation] -> ShowS # | |
Eq TermsAggregation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: TermsAggregation -> TermsAggregation -> Bool # (/=) :: TermsAggregation -> TermsAggregation -> Bool # |
data CardinalityAggregation Source #
Instances
data DateHistogramAggregation Source #
Instances
data DateRangeAggregation Source #
Instances
data DateRangeAggRange Source #
Instances
ToJSON DateRangeAggRange Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation toJSON :: DateRangeAggRange -> Value # toEncoding :: DateRangeAggRange -> Encoding # toJSONList :: [DateRangeAggRange] -> Value # toEncodingList :: [DateRangeAggRange] -> Encoding # omitField :: DateRangeAggRange -> Bool # | |
Show DateRangeAggRange Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> DateRangeAggRange -> ShowS # show :: DateRangeAggRange -> String # showList :: [DateRangeAggRange] -> ShowS # | |
Eq DateRangeAggRange Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: DateRangeAggRange -> DateRangeAggRange -> Bool # (/=) :: DateRangeAggRange -> DateRangeAggRange -> Bool # |
data ValueCountAggregation Source #
See https://www.elastic.co/guide/en/elasticsearch/reference/current/search-aggregations-metrics-valuecount-aggregation.html for more information.
Instances
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.
Instances
Show FilterAggregation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> FilterAggregation -> ShowS # show :: FilterAggregation -> String # showList :: [FilterAggregation] -> ShowS # | |
Eq FilterAggregation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: FilterAggregation -> FilterAggregation -> Bool # (/=) :: FilterAggregation -> FilterAggregation -> Bool # |
data StatisticsAggregation Source #
Instances
newtype SumAggregation Source #
Instances
Show SumAggregation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> SumAggregation -> ShowS # show :: SumAggregation -> String # showList :: [SumAggregation] -> ShowS # | |
Eq SumAggregation Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: SumAggregation -> SumAggregation -> Bool # (/=) :: SumAggregation -> SumAggregation -> Bool # |
class BucketAggregation a where Source #
key :: a -> BucketValue Source #
aggs :: a -> Maybe AggregationResults Source #
bucketsLens :: Lens' (Bucket a) [a] Source #
data BucketValue Source #
Instances
FromJSON BucketValue Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation parseJSON :: Value -> Parser BucketValue # parseJSONList :: Value -> Parser [BucketValue] # | |
Read BucketValue Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation readsPrec :: Int -> ReadS BucketValue # readList :: ReadS [BucketValue] # readPrec :: ReadPrec BucketValue # readListPrec :: ReadPrec [BucketValue] # | |
Show BucketValue Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> BucketValue -> ShowS # show :: BucketValue -> String # showList :: [BucketValue] -> ShowS # |
data TermInclusion Source #
Instances
ToJSON TermInclusion Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation toJSON :: TermInclusion -> Value # toEncoding :: TermInclusion -> Encoding # toJSONList :: [TermInclusion] -> Value # toEncodingList :: [TermInclusion] -> Encoding # omitField :: TermInclusion -> Bool # | |
Show TermInclusion Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> TermInclusion -> ShowS # show :: TermInclusion -> String # showList :: [TermInclusion] -> ShowS # | |
Eq TermInclusion Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: TermInclusion -> TermInclusion -> Bool # (/=) :: TermInclusion -> TermInclusion -> Bool # |
data CollectionMode Source #
Instances
ToJSON CollectionMode Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation toJSON :: CollectionMode -> Value # toEncoding :: CollectionMode -> Encoding # toJSONList :: [CollectionMode] -> Value # toEncodingList :: [CollectionMode] -> Encoding # omitField :: CollectionMode -> Bool # | |
Show CollectionMode Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> CollectionMode -> ShowS # show :: CollectionMode -> String # showList :: [CollectionMode] -> ShowS # | |
Eq CollectionMode Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: CollectionMode -> CollectionMode -> Bool # (/=) :: CollectionMode -> CollectionMode -> Bool # |
data ExecutionHint Source #
Instances
ToJSON ExecutionHint Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation toJSON :: ExecutionHint -> Value # toEncoding :: ExecutionHint -> Encoding # toJSONList :: [ExecutionHint] -> Value # toEncodingList :: [ExecutionHint] -> Encoding # omitField :: ExecutionHint -> Bool # | |
Show ExecutionHint Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> ExecutionHint -> ShowS # show :: ExecutionHint -> String # showList :: [ExecutionHint] -> ShowS # | |
Eq ExecutionHint Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: ExecutionHint -> ExecutionHint -> Bool # (/=) :: ExecutionHint -> ExecutionHint -> Bool # |
data DateMathExpr Source #
See https://www.elastic.co/guide/en/elasticsearch/reference/current/common-options.html#date-math for more information.
Instances
ToJSON DateMathExpr Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation toJSON :: DateMathExpr -> Value # toEncoding :: DateMathExpr -> Encoding # toJSONList :: [DateMathExpr] -> Value # toEncodingList :: [DateMathExpr] -> Encoding # omitField :: DateMathExpr -> Bool # | |
Show DateMathExpr Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> DateMathExpr -> ShowS # show :: DateMathExpr -> String # showList :: [DateMathExpr] -> ShowS # | |
Eq DateMathExpr Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: DateMathExpr -> DateMathExpr -> Bool # (/=) :: DateMathExpr -> DateMathExpr -> Bool # |
data DateMathAnchor Source #
Starting point for a date range. This along with the DateMathModifiers
gets you the date ES will start from.
Instances
Show DateMathAnchor Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> DateMathAnchor -> ShowS # show :: DateMathAnchor -> String # showList :: [DateMathAnchor] -> ShowS # | |
Eq DateMathAnchor Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: DateMathAnchor -> DateMathAnchor -> Bool # (/=) :: DateMathAnchor -> DateMathAnchor -> Bool # |
data DateMathModifier Source #
Instances
Show DateMathModifier Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> DateMathModifier -> ShowS # show :: DateMathModifier -> String # showList :: [DateMathModifier] -> ShowS # | |
Eq DateMathModifier Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: DateMathModifier -> DateMathModifier -> Bool # (/=) :: DateMathModifier -> DateMathModifier -> Bool # |
data DateMathUnit Source #
Instances
Show DateMathUnit Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> DateMathUnit -> ShowS # show :: DateMathUnit -> String # showList :: [DateMathUnit] -> ShowS # | |
Eq DateMathUnit Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: DateMathUnit -> DateMathUnit -> Bool # (/=) :: DateMathUnit -> DateMathUnit -> Bool # |
data TermsResult Source #
Instances
FromJSON TermsResult Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation parseJSON :: Value -> Parser TermsResult # parseJSONList :: Value -> Parser [TermsResult] # | |
Read TermsResult Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation readsPrec :: Int -> ReadS TermsResult # readList :: ReadS [TermsResult] # readPrec :: ReadPrec TermsResult # readListPrec :: ReadPrec [TermsResult] # | |
Show TermsResult Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> TermsResult -> ShowS # show :: TermsResult -> String # showList :: [TermsResult] -> ShowS # | |
BucketAggregation TermsResult Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation key :: TermsResult -> BucketValue Source # docCount :: TermsResult -> Int Source # |
data DateHistogramResult Source #
DateHistogramResult | |
|
Instances
data DateRangeResult Source #
Instances
toTerms :: Key -> AggregationResults -> Maybe (Bucket TermsResult) Source #
toMissing :: Key -> AggregationResults -> Maybe MissingResult Source #
toTopHits :: FromJSON a => Key -> AggregationResults -> Maybe (TopHitResult a) Source #
toAggResult :: FromJSON a => Key -> AggregationResults -> Maybe a Source #
getNamedSubAgg :: Object -> [Key] -> Maybe AggregationResults Source #
data MissingResult Source #
Instances
FromJSON MissingResult Source # | |
Show MissingResult Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> MissingResult -> ShowS # show :: MissingResult -> String # showList :: [MissingResult] -> ShowS # |
data TopHitResult a Source #
Instances
FromJSON a => FromJSON (TopHitResult a) Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation parseJSON :: Value -> Parser (TopHitResult a) # parseJSONList :: Value -> Parser [TopHitResult a] # omittedField :: Maybe (TopHitResult a) # | |
Show a => Show (TopHitResult a) Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation showsPrec :: Int -> TopHitResult a -> ShowS # show :: TopHitResult a -> String # showList :: [TopHitResult a] -> ShowS # | |
Eq a => Eq (TopHitResult a) Source # | |
Defined in Database.Bloodhound.Internal.Versions.Common.Types.Aggregation (==) :: TopHitResult a -> TopHitResult a -> Bool # (/=) :: TopHitResult a -> TopHitResult a -> Bool # |
data HitsTotalRelation Source #
Instances
data SearchHits a Source #
Instances
searchHitsHitsLens :: Lens' (SearchHits a) [Hit a] Source #
type SearchAfterKey = [Value] Source #
Hit | |
|
hitSortLens :: Lens' (Hit a) (Maybe SearchAfterKey) Source #
hitHighlightLens :: Lens' (Hit a) (Maybe HitHighlight) Source #
hitInnerHitsLens :: Lens' (Hit a) (Maybe (KeyMap (TopHitResult Value))) Source #
newtype 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.
Instances
mkDocVersion :: Int -> Maybe DocVersion Source #
Smart constructor for in-range doc version
data VersionControl Source #
VersionControl
is specified when indexing documents as a
optimistic concurrency control.
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
Show VersionControl Source # | |
Defined in Database.Bloodhound.Internal.Client.Doc showsPrec :: Int -> VersionControl -> ShowS # show :: VersionControl -> String # showList :: [VersionControl] -> ShowS # | |
Eq VersionControl Source # | |
Defined in Database.Bloodhound.Internal.Client.Doc (==) :: VersionControl -> VersionControl -> Bool # (/=) :: VersionControl -> VersionControl -> Bool # | |
Ord VersionControl Source # | |
Defined in Database.Bloodhound.Internal.Client.Doc compare :: VersionControl -> VersionControl -> Ordering # (<) :: VersionControl -> VersionControl -> Bool # (<=) :: VersionControl -> VersionControl -> Bool # (>) :: VersionControl -> VersionControl -> Bool # (>=) :: VersionControl -> VersionControl -> Bool # max :: VersionControl -> VersionControl -> VersionControl # min :: VersionControl -> VersionControl -> VersionControl # |
Request
data BHRequest parsingContext responseBody Source #
Request
upon Elasticsearch's server.
parsingContext
is a phantom type for the expected status-dependancy
responseBody
is a phantom type for the expected result
BHRequest | |
|
mkFullRequest :: (ParseBHResponse parsingContext, FromJSON responseBody) => Method -> Endpoint -> ByteString -> BHRequest parsingContext responseBody Source #
BHRequest
with a body
mkSimpleRequest :: (ParseBHResponse parsingContext, FromJSON responseBody) => Method -> Endpoint -> BHRequest parsingContext responseBody Source #
BHRequest
without a body
type ParsedEsResponse a = Either EsError a Source #
Result of a parseEsResponse
class ParseBHResponse parsingContext where Source #
parseBHResponse :: FromJSON a => BHResponse parsingContext a -> Either EsProtocolException (ParsedEsResponse a) Source #
Instances
Server
is used with the client functions to point at the ES instance
Endpoint
represents an url before being built
Endpoint | |
|
withQueries :: Endpoint -> [(Text, Maybe Text)] -> Endpoint Source #
Severely dumbed down query renderer. Assumes your data doesn't need any encoding
withBHResponse :: forall a parsingContext b. (Either EsProtocolException (ParsedEsResponse a) -> BHResponse StatusDependant a -> b) -> BHRequest parsingContext a -> BHRequest StatusDependant b Source #
Work with the full BHResponse
withBHResponse_ :: forall a parsingContext b. (BHResponse StatusDependant a -> b) -> BHRequest parsingContext a -> BHRequest StatusDependant b Source #
Work with the full BHResponse
withBHResponseParsedEsResponse :: forall a parsingContext. BHRequest parsingContext a -> BHRequest StatusDependant (ParsedEsResponse a) Source #
Enable working with ParsedEsResponse
keepBHResponse :: forall a parsingContext. BHRequest parsingContext a -> BHRequest StatusDependant (BHResponse StatusDependant a, a) Source #
Keep with the full BHResponse
joinBHResponse :: forall a parsingContext. BHRequest parsingContext (Either EsProtocolException (ParsedEsResponse a)) -> BHRequest parsingContext a Source #
Response
newtype BHResponse parsingContext body Source #
Result of a BHRequest
Instances
Show (BHResponse parsingContext body) Source # | |
Defined in Database.Bloodhound.Internal.Client.BHRequest showsPrec :: Int -> BHResponse parsingContext body -> ShowS # show :: BHResponse parsingContext body -> String # showList :: [BHResponse parsingContext body] -> ShowS # |
Response interpretation
decodeResponse :: FromJSON a => BHResponse StatusIndependant a -> Maybe a Source #
Helper around aeson
decode
eitherDecodeResponse :: FromJSON a => BHResponse StatusIndependant a -> Either String a Source #
Helper around aeson
eitherDecode
parseEsResponse :: FromJSON body => BHResponse parsingContext body -> Either EsProtocolException (ParsedEsResponse body) Source #
Tries to parse a response body as the expected type body
and
failing that tries to parse it as an EsError. All well-formed, JSON
responses from elasticsearch should fall into these two
categories. If they don't, a EsProtocolException
will be
thrown. If you encounter this, please report the full body it
reports along with your Elasticsearch version.
parseEsResponseWith :: (MonadThrow m, FromJSON body) => (body -> Either String parsed) -> BHResponse parsingContext body -> m parsed Source #
Parse BHResponse
with an arbitrary parser
isVersionConflict :: BHResponse parsingContext a -> Bool Source #
Was there an optimistic concurrency control conflict when indexing a document?
isSuccess :: BHResponse parsingContext a -> Bool Source #
Check '2xx' status codes
isCreated :: BHResponse parsingContext a -> Bool Source #
Check '201' status code
statusCodeIs :: (Int, Int) -> BHResponse parsingContext body -> Bool Source #
Check status code in range
Response handling
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.
Instances
Exception EsProtocolException Source # | |
Show EsProtocolException Source # | |
Defined in Database.Bloodhound.Internal.Client.BHRequest showsPrec :: Int -> EsProtocolException -> ShowS # show :: EsProtocolException -> String # showList :: [EsProtocolException] -> ShowS # | |
Eq EsProtocolException Source # | |
Defined in Database.Bloodhound.Internal.Client.BHRequest (==) :: EsProtocolException -> EsProtocolException -> Bool # (/=) :: EsProtocolException -> EsProtocolException -> Bool # |
EsResult
describes the standard wrapper JSON document that you see in
successful Elasticsearch lookups or lookups that couldn't find the document.
EsResult | |
|
data EsResultFound a Source #
EsResultFound
contains the document and its metadata inside of an
EsResult
when the document was successfully found.
EsResultFound | |
|
Instances
FromJSON a => FromJSON (EsResultFound a) Source # | |
Defined in Database.Bloodhound.Internal.Client.BHRequest parseJSON :: Value -> Parser (EsResultFound a) # parseJSONList :: Value -> Parser [EsResultFound a] # omittedField :: Maybe (EsResultFound a) # | |
Show a => Show (EsResultFound a) Source # | |
Defined in Database.Bloodhound.Internal.Client.BHRequest showsPrec :: Int -> EsResultFound a -> ShowS # show :: EsResultFound a -> String # showList :: [EsResultFound a] -> ShowS # | |
Eq a => Eq (EsResultFound a) Source # | |
Defined in Database.Bloodhound.Internal.Client.BHRequest (==) :: EsResultFound a -> EsResultFound a -> Bool # (/=) :: EsResultFound a -> EsResultFound a -> Bool # |
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.
EsError | |
|
Instances
Common results
newtype Acknowledged Source #
Instances
FromJSON Acknowledged Source # | |
Defined in Database.Bloodhound.Internal.Client.BHRequest parseJSON :: Value -> Parser Acknowledged # parseJSONList :: Value -> Parser [Acknowledged] # | |
Show Acknowledged Source # | |
Defined in Database.Bloodhound.Internal.Client.BHRequest showsPrec :: Int -> Acknowledged -> ShowS # show :: Acknowledged -> String # showList :: [Acknowledged] -> ShowS # | |
Eq Acknowledged Source # | |
Defined in Database.Bloodhound.Internal.Client.BHRequest (==) :: Acknowledged -> Acknowledged -> Bool # (/=) :: Acknowledged -> Acknowledged -> Bool # |
data IgnoredBody Source #
Instances
FromJSON IgnoredBody Source # | |
Defined in Database.Bloodhound.Internal.Client.BHRequest parseJSON :: Value -> Parser IgnoredBody # parseJSONList :: Value -> Parser [IgnoredBody] # | |
Show IgnoredBody Source # | |
Defined in Database.Bloodhound.Internal.Client.BHRequest showsPrec :: Int -> IgnoredBody -> ShowS # show :: IgnoredBody -> String # showList :: [IgnoredBody] -> ShowS # | |
Eq IgnoredBody Source # | |
Defined in Database.Bloodhound.Internal.Client.BHRequest (==) :: IgnoredBody -> IgnoredBody -> Bool # (/=) :: IgnoredBody -> IgnoredBody -> Bool # |