| 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 | None |
| Language | Haskell2010 |
Database.Bloodhound.Client
Description
Client side functions for talking to Elasticsearch servers.
Synopsis
- withBH :: ManagerSettings -> Server -> BH IO a -> IO a
- createIndex :: MonadBH m => IndexSettings -> IndexName -> m (BHResponse Acknowledged)
- createIndexWith :: MonadBH m => [UpdatableIndexSetting] -> Int -> IndexName -> m (BHResponse Acknowledged)
- flushIndex :: MonadBH m => IndexName -> m (BHResponse ShardResult)
- deleteIndex :: MonadBH m => IndexName -> m (BHResponse Acknowledged)
- updateIndexSettings :: MonadBH m => NonEmpty UpdatableIndexSetting -> IndexName -> m (BHResponse Acknowledged)
- getIndexSettings :: (MonadBH m, MonadThrow m) => IndexName -> m (ParsedEsResponse IndexSettingsSummary)
- forceMergeIndex :: MonadBH m => IndexSelection -> ForceMergeIndexSettings -> m (BHResponse ShardCount)
- indexExists :: MonadBH m => IndexName -> m Bool
- openIndex :: MonadBH m => IndexName -> m (BHResponse Acknowledged)
- closeIndex :: MonadBH m => IndexName -> m (BHResponse Acknowledged)
- listIndices :: (MonadThrow m, MonadBH m) => m [IndexName]
- catIndices :: (MonadThrow m, MonadBH m) => m [(IndexName, Int)]
- waitForYellowIndex :: MonadBH m => IndexName -> m (BHResponse HealthStatus)
- data HealthStatus = HealthStatus {
- healthStatusClusterName :: Text
- healthStatusStatus :: Text
- healthStatusTimedOut :: Bool
- healthStatusNumberOfNodes :: Int
- healthStatusNumberOfDataNodes :: Int
- healthStatusActivePrimaryShards :: Int
- healthStatusActiveShards :: Int
- healthStatusRelocatingShards :: Int
- healthStatusInitializingShards :: Int
- healthStatusUnassignedShards :: Int
- healthStatusDelayedUnassignedShards :: Int
- healthStatusNumberOfPendingTasks :: Int
- healthStatusNumberOfInFlightFetch :: Int
- healthStatusTaskMaxWaitingInQueueMillis :: Int
- healthStatusActiveShardsPercentAsNumber :: Float
- updateIndexAliases :: MonadBH m => NonEmpty IndexAliasAction -> m (BHResponse Acknowledged)
- getIndexAliases :: (MonadBH m, MonadThrow m) => m (ParsedEsResponse IndexAliasesSummary)
- deleteIndexAlias :: MonadBH m => IndexAliasName -> m (BHResponse Acknowledged)
- putTemplate :: MonadBH m => IndexTemplate -> TemplateName -> m (BHResponse Acknowledged)
- templateExists :: MonadBH m => TemplateName -> m Bool
- deleteTemplate :: MonadBH m => TemplateName -> m (BHResponse Acknowledged)
- putMapping :: (MonadBH m, ToJSON a) => IndexName -> a -> m (BHResponse a)
- indexDocument :: (ToJSON doc, MonadBH m) => IndexName -> IndexDocumentSettings -> doc -> DocId -> m (BHResponse IndexedDocument)
- updateDocument :: (ToJSON patch, MonadBH m) => IndexName -> IndexDocumentSettings -> patch -> DocId -> m (BHResponse IndexedDocument)
- getDocument :: (FromJSON a, MonadBH m) => IndexName -> DocId -> m (BHResponse (EsResult a))
- documentExists :: MonadBH m => IndexName -> DocId -> m Bool
- deleteDocument :: MonadBH m => IndexName -> DocId -> m (BHResponse IndexedDocument)
- deleteByQuery :: MonadBH m => IndexName -> Query -> m (BHResponse DeletedDocuments)
- data IndexedDocument = IndexedDocument {}
- data DeletedDocuments = DeletedDocuments {
- delDocsTook :: Int
- delDocsTimedOut :: Bool
- delDocsTotal :: Int
- delDocsDeleted :: Int
- delDocsBatches :: Int
- delDocsVersionConflicts :: Int
- delDocsNoops :: Int
- delDocsRetries :: DeletedDocumentsRetries
- delDocsThrottledMillis :: Int
- delDocsRequestsPerSecond :: Float
- delDocsThrottledUntilMillis :: Int
- delDocsFailures :: [Value]
- data DeletedDocumentsRetries = DeletedDocumentsRetries {}
- searchAll :: MonadBH m => Search -> m (BHResponse (SearchResult a))
- searchByIndex :: MonadBH m => IndexName -> Search -> m (BHResponse (SearchResult a))
- searchByIndices :: MonadBH m => NonEmpty IndexName -> Search -> m (BHResponse (SearchResult a))
- searchByIndexTemplate :: (FromJSON a, MonadBH m) => IndexName -> SearchTemplate -> m (BHResponse (SearchResult a))
- searchByIndicesTemplate :: (FromJSON a, MonadBH m) => NonEmpty IndexName -> SearchTemplate -> m (BHResponse (SearchResult a))
- scanSearch :: (FromJSON a, MonadBH m, MonadThrow m) => IndexName -> Search -> m [Hit a]
- getInitialScroll :: (FromJSON a, MonadThrow m, MonadBH m) => IndexName -> Search -> m (ParsedEsResponse (SearchResult a))
- getInitialSortedScroll :: (FromJSON a, MonadThrow m, MonadBH m) => IndexName -> Search -> m (ParsedEsResponse (SearchResult a))
- advanceScroll :: (FromJSON a, MonadBH m, MonadThrow m) => ScrollId -> NominalDiffTime -> m (ParsedEsResponse (SearchResult a))
- pitSearch :: (FromJSON a, MonadBH m, MonadThrow m, Show a) => IndexName -> Search -> m [Hit a]
- openPointInTime :: (MonadBH m, MonadThrow m) => IndexName -> m (ParsedEsResponse OpenPointInTimeResponse)
- closePointInTime :: (MonadBH m, MonadThrow m) => ClosePointInTime -> m (ParsedEsResponse ClosePointInTimeResponse)
- refreshIndex :: MonadBH m => IndexName -> m (BHResponse ShardResult)
- mkSearch :: Maybe Query -> Maybe Filter -> Search
- mkAggregateSearch :: Maybe Query -> Aggregations -> Search
- mkHighlightSearch :: Maybe Query -> Highlights -> Search
- mkSearchTemplate :: Either SearchTemplateId SearchTemplateSource -> TemplateQueryKeyValuePairs -> SearchTemplate
- bulk :: MonadBH m => Vector BulkOperation -> m (BHResponse a)
- pageSearch :: From -> Size -> Search -> Search
- mkShardCount :: Int -> Maybe ShardCount
- mkReplicaCount :: Int -> Maybe ReplicaCount
- getStatus :: MonadBH m => m (Either String Status)
- storeSearchTemplate :: MonadBH m => SearchTemplateId -> SearchTemplateSource -> m (BHResponse Acknowledged)
- getSearchTemplate :: MonadBH m => SearchTemplateId -> m (BHResponse GetTemplateScript)
- deleteSearchTemplate :: MonadBH m => SearchTemplateId -> m (BHResponse Acknowledged)
- getSnapshotRepos :: (MonadBH m, MonadThrow m) => SnapshotRepoSelection -> m (ParsedEsResponse [GenericSnapshotRepo])
- updateSnapshotRepo :: (MonadBH m, SnapshotRepo repo) => SnapshotRepoUpdateSettings -> repo -> m (BHResponse Acknowledged)
- verifySnapshotRepo :: (MonadBH m, MonadThrow m) => SnapshotRepoName -> m (ParsedEsResponse SnapshotVerification)
- deleteSnapshotRepo :: MonadBH m => SnapshotRepoName -> m (BHResponse Acknowledged)
- createSnapshot :: MonadBH m => SnapshotRepoName -> SnapshotName -> SnapshotCreateSettings -> m (BHResponse Acknowledged)
- getSnapshots :: (MonadBH m, MonadThrow m) => SnapshotRepoName -> SnapshotSelection -> m (ParsedEsResponse [SnapshotInfo])
- deleteSnapshot :: MonadBH m => SnapshotRepoName -> SnapshotName -> m (BHResponse Acknowledged)
- restoreSnapshot :: MonadBH m => SnapshotRepoName -> SnapshotName -> SnapshotRestoreSettings -> m (BHResponse Accepted)
- getNodesInfo :: (MonadBH m, MonadThrow m) => NodeSelection -> m (ParsedEsResponse NodesInfo)
- getNodesStats :: (MonadBH m, MonadThrow m) => NodeSelection -> m (ParsedEsResponse NodesStats)
- encodeBulkOperations :: Vector BulkOperation -> ByteString
- encodeBulkOperation :: BulkOperation -> ByteString
- basicAuthHook :: Monad m => EsUsername -> EsPassword -> Request -> m Request
- isVersionConflict :: BHResponse a -> Bool
- isSuccess :: BHResponse a -> Bool
- isCreated :: BHResponse a -> Bool
- parseEsResponse :: (MonadThrow m, FromJSON body) => BHResponse body -> m (ParsedEsResponse body)
- parseEsResponseWith :: (MonadThrow m, FromJSON body) => (body -> Either String parsed) -> BHResponse body -> m parsed
- decodeResponse :: FromJSON a => BHResponse a -> Maybe a
- eitherDecodeResponse :: FromJSON a => BHResponse a -> Either String a
- countByIndex :: (MonadBH m, MonadThrow m) => IndexName -> CountQuery -> m (ParsedEsResponse CountResponse)
- newtype Acknowledged = Acknowledged {}
- newtype Accepted = Accepted {
- isAccepted :: Bool
Bloodhound client functions
The examples in this module assume the following code has been run. The :{ and :} will only work in GHCi. You'll only need the data types and typeclass instances for the functions that make use of them.
>>>:set -XOverloadedStrings>>>:set -XDeriveGeneric>>>import Database.Bloodhound>>>import Network.HTTP.Client>>>let testServer = (Server "http://localhost:9200")>>>let runBH' = withBH defaultManagerSettings testServer>>>let testIndex = IndexName "twitter">>>let defaultIndexSettings = IndexSettings (ShardCount 1) (ReplicaCount 0)>>>data TweetMapping = TweetMapping deriving (Eq, Show)>>>_ <- runBH' $ deleteIndex testIndex>>>_ <- runBH' $ deleteIndex (IndexName "didimakeanindex")>>>import GHC.Generics>>>import Data.Time.Calendar (Day (..))>>>import Data.Time.Clock (UTCTime (..), secondsToDiffTime)>>>:{instance ToJSON TweetMapping where toJSON TweetMapping = object ["properties" .= object ["location" .= object ["type" .= ("geo_point" :: Text)]]] data Location = Location { lat :: Double , lon :: Double } deriving (Eq, Generic, Show) data Tweet = Tweet { user :: Text , postDate :: UTCTime , message :: Text , age :: Int , location :: Location } deriving (Eq, Generic, Show) exampleTweet = Tweet { user = "bitemyapp" , postDate = UTCTime (ModifiedJulianDay 55000) (secondsToDiffTime 10) , message = "Use haskell!" , age = 10000 , location = Location 40.12 (-71.34) } instance ToJSON Tweet where toJSON = genericToJSON defaultOptions instance FromJSON Tweet where parseJSON = genericParseJSON defaultOptions instance ToJSON Location where toJSON = genericToJSON defaultOptions instance FromJSON Location where parseJSON = genericParseJSON defaultOptions data BulkTest = BulkTest { name :: Text } deriving (Eq, Generic, Show) instance FromJSON BulkTest where parseJSON = genericParseJSON defaultOptions instance ToJSON BulkTest where toJSON = genericToJSON defaultOptions :}
withBH :: ManagerSettings -> Server -> BH IO a -> IO a Source #
Convenience function that sets up a manager and BHEnv and runs
the given set of bloodhound operations. Connections will be
pipelined automatically in accordance with the given manager
settings in IO. If you've got your own monad transformer stack, you
should use runBH directly.
Indices
createIndex :: MonadBH m => IndexSettings -> IndexName -> m (BHResponse Acknowledged) Source #
createIndex will create an index given a Server, IndexSettings, and an IndexName.
>>>response <- runBH' $ createIndex defaultIndexSettings (IndexName "didimakeanindex")>>>isSuccess responseTrue>>>runBH' $ indexExists (IndexName "didimakeanindex")True
Arguments
| :: MonadBH m | |
| => [UpdatableIndexSetting] | |
| -> Int | shard count |
| -> IndexName | |
| -> m (BHResponse Acknowledged) |
Create an index, providing it with any number of settings. This
is more expressive than createIndex but makes is more verbose
for the common case of configuring only the shard count and
replica count.
flushIndex :: MonadBH m => IndexName -> m (BHResponse ShardResult) Source #
flushIndex will flush an index given a Server and an IndexName.
deleteIndex :: MonadBH m => IndexName -> m (BHResponse Acknowledged) Source #
deleteIndex will delete an index given a Server and an IndexName.
>>>_ <- runBH' $ createIndex defaultIndexSettings (IndexName "didimakeanindex")>>>response <- runBH' $ deleteIndex (IndexName "didimakeanindex")>>>isSuccess responseTrue>>>runBH' $ indexExists (IndexName "didimakeanindex")False
updateIndexSettings :: MonadBH m => NonEmpty UpdatableIndexSetting -> IndexName -> m (BHResponse Acknowledged) Source #
updateIndexSettings will apply a non-empty list of setting updates to an index
>>>_ <- runBH' $ createIndex defaultIndexSettings (IndexName "unconfiguredindex")>>>response <- runBH' $ updateIndexSettings (BlocksWrite False :| []) (IndexName "unconfiguredindex")>>>isSuccess responseTrue
getIndexSettings :: (MonadBH m, MonadThrow m) => IndexName -> m (ParsedEsResponse IndexSettingsSummary) Source #
forceMergeIndex :: MonadBH m => IndexSelection -> ForceMergeIndexSettings -> m (BHResponse ShardCount) Source #
The force merge API allows to force merging of one or more indices through an API. The merge relates to the number of segments a Lucene index holds within each shard. The force merge operation allows to reduce the number of segments by merging them.
This call will block until the merge is complete. If the http connection is lost, the request will continue in the background, and any new requests will block until the previous force merge is complete.
indexExists :: MonadBH m => IndexName -> m Bool Source #
indexExists enables you to check if an index exists. Returns Bool
in IO
>>>exists <- runBH' $ indexExists testIndex
openIndex :: MonadBH m => IndexName -> m (BHResponse Acknowledged) Source #
openIndex opens an index given a Server and an IndexName. Explained in further detail at
http://www.elastic.co/guide/en/elasticsearch/reference/current/indices-open-close.html
>>>response <- runBH' $ openIndex testIndex
closeIndex :: MonadBH m => IndexName -> m (BHResponse Acknowledged) Source #
closeIndex closes an index given a Server and an IndexName. Explained in further detail at
http://www.elastic.co/guide/en/elasticsearch/reference/current/indices-open-close.html
>>>response <- runBH' $ closeIndex testIndex
listIndices :: (MonadThrow m, MonadBH m) => m [IndexName] Source #
listIndices returns a list of all index names on a given Server
catIndices :: (MonadThrow m, MonadBH m) => m [(IndexName, Int)] Source #
catIndices returns a list of all index names on a given Server as well as their doc counts
waitForYellowIndex :: MonadBH m => IndexName -> m (BHResponse HealthStatus) Source #
Block until the index becomes available for indexing documents. This is useful for integration tests in which indices are rapidly created and deleted.
data HealthStatus Source #
Constructors
Instances
| Eq HealthStatus Source # | |
Defined in Database.Bloodhound.Client | |
| Show HealthStatus Source # | |
Defined in Database.Bloodhound.Client Methods showsPrec :: Int -> HealthStatus -> ShowS # show :: HealthStatus -> String # showList :: [HealthStatus] -> ShowS # | |
| FromJSON HealthStatus Source # | |
Defined in Database.Bloodhound.Client | |
Index Aliases
updateIndexAliases :: MonadBH m => NonEmpty IndexAliasAction -> m (BHResponse Acknowledged) Source #
updateIndexAliases updates the server's index alias
table. Operations are atomic. Explained in further detail at
https://www.elastic.co/guide/en/elasticsearch/reference/current/indices-aliases.html
>>>let src = IndexName "a-real-index">>>let aliasName = IndexName "an-alias">>>let iAlias = IndexAlias src (IndexAliasName aliasName)>>>let aliasCreate = IndexAliasCreate Nothing Nothing>>>_ <- runBH' $ deleteIndex src>>>isSuccess <$> runBH' (createIndex defaultIndexSettings src)True>>>runBH' $ indexExists srcTrue>>>isSuccess <$> runBH' (updateIndexAliases (AddAlias iAlias aliasCreate :| []))True>>>runBH' $ indexExists aliasNameTrue
getIndexAliases :: (MonadBH m, MonadThrow m) => m (ParsedEsResponse IndexAliasesSummary) Source #
Get all aliases configured on the server.
deleteIndexAlias :: MonadBH m => IndexAliasName -> m (BHResponse Acknowledged) Source #
Delete a single alias, removing it from all indices it is currently associated with.
Index Templates
putTemplate :: MonadBH m => IndexTemplate -> TemplateName -> m (BHResponse Acknowledged) Source #
putTemplate creates a template given an IndexTemplate and a TemplateName.
Explained in further detail at
https://www.elastic.co/guide/en/elasticsearch/reference/1.7/indices-templates.html
>>>let idxTpl = IndexTemplate [IndexPattern "tweet-*"] (Just (IndexSettings (ShardCount 1) (ReplicaCount 1))) [toJSON TweetMapping]>>>resp <- runBH' $ putTemplate idxTpl (TemplateName "tweet-tpl")
templateExists :: MonadBH m => TemplateName -> m Bool Source #
templateExists checks to see if a template exists.
>>>exists <- runBH' $ templateExists (TemplateName "tweet-tpl")
deleteTemplate :: MonadBH m => TemplateName -> m (BHResponse Acknowledged) Source #
deleteTemplate is an HTTP DELETE and deletes a template.
>>>let idxTpl = IndexTemplate [IndexPattern "tweet-*"] (Just (IndexSettings (ShardCount 1) (ReplicaCount 1))) [toJSON TweetMapping]>>>_ <- runBH' $ putTemplate idxTpl (TemplateName "tweet-tpl")>>>resp <- runBH' $ deleteTemplate (TemplateName "tweet-tpl")
Mapping
putMapping :: (MonadBH m, ToJSON a) => IndexName -> a -> m (BHResponse a) Source #
putMapping is an HTTP PUT and has upsert semantics. Mappings are schemas
for documents in indexes.
>>>_ <- runBH' $ createIndex defaultIndexSettings testIndex>>>resp <- runBH' $ putMapping testIndex TweetMapping>>>print respResponse {responseStatus = Status {statusCode = 200, statusMessage = "OK"}, responseVersion = HTTP/1.1, responseHeaders = [("content-type","application/json; charset=UTF-8"),("content-encoding","gzip"),("transfer-encoding","chunked")], responseBody = "{\"acknowledged\":true}", responseCookieJar = CJ {expose = []}, responseClose' = ResponseClose}
Documents
indexDocument :: (ToJSON doc, MonadBH m) => IndexName -> IndexDocumentSettings -> doc -> DocId -> m (BHResponse IndexedDocument) Source #
indexDocument is the primary way to save a single document in
Elasticsearch. The document itself is simply something we can
convert into a JSON Value. The DocId will function as the
primary key for the document. You are encouraged to generate
your own id's and not rely on Elasticsearch's automatic id
generation. Read more about it here:
https://github.com/bitemyapp/bloodhound/issues/107
>>>resp <- runBH' $ indexDocument testIndex defaultIndexDocumentSettings exampleTweet (DocId "1")>>>print respResponse {responseStatus = Status {statusCode = 200, statusMessage = "OK"}, responseVersion = HTTP/1.1, responseHeaders = [("content-type","application/json; charset=UTF-8"),("content-encoding","gzip"),("content-length","152")], responseBody = "{\"_index\":\"bloodhound-tests-twitter-1\",\"_type\":\"_doc\",\"_id\":\"1\",\"_version\":2,\"result\":\"updated\",\"_shards\":{\"total\":1,\"successful\":1,\"failed\":0},\"_seq_no\":1,\"_primary_term\":1}", responseCookieJar = CJ {expose = []}, responseClose' = ResponseClose}
updateDocument :: (ToJSON patch, MonadBH m) => IndexName -> IndexDocumentSettings -> patch -> DocId -> m (BHResponse IndexedDocument) Source #
updateDocument provides a way to perform an partial update of a
an already indexed document.
getDocument :: (FromJSON a, MonadBH m) => IndexName -> DocId -> m (BHResponse (EsResult a)) Source #
getDocument is a straight-forward way to fetch a single document from
Elasticsearch using a Server, IndexName, and a DocId.
The DocId is the primary key for your Elasticsearch document.
>>>yourDoc <- runBH' $ getDocument testIndex (DocId "1")
documentExists :: MonadBH m => IndexName -> DocId -> m Bool Source #
documentExists enables you to check if a document exists.
deleteDocument :: MonadBH m => IndexName -> DocId -> m (BHResponse IndexedDocument) Source #
deleteDocument is the primary way to delete a single document.
>>>_ <- runBH' $ deleteDocument testIndex (DocId "1")
deleteByQuery :: MonadBH m => IndexName -> Query -> m (BHResponse DeletedDocuments) Source #
deleteByQuery performs a deletion on every document that matches a query.
>>>let query = TermQuery (Term "user" "bitemyapp") Nothing>>>_ <- runBH' $ deleteDocument testIndex query
data IndexedDocument Source #
Constructors
| IndexedDocument | |
Fields
| |
Instances
| Eq IndexedDocument Source # | |
Defined in Database.Bloodhound.Client Methods (==) :: IndexedDocument -> IndexedDocument -> Bool # (/=) :: IndexedDocument -> IndexedDocument -> Bool # | |
| Show IndexedDocument Source # | |
Defined in Database.Bloodhound.Client Methods showsPrec :: Int -> IndexedDocument -> ShowS # show :: IndexedDocument -> String # showList :: [IndexedDocument] -> ShowS # | |
| FromJSON IndexedDocument Source # | |
Defined in Database.Bloodhound.Client Methods parseJSON :: Value -> Parser IndexedDocument # parseJSONList :: Value -> Parser [IndexedDocument] # | |
data DeletedDocuments Source #
Constructors
Instances
| Eq DeletedDocuments Source # | |
Defined in Database.Bloodhound.Client Methods (==) :: DeletedDocuments -> DeletedDocuments -> Bool # (/=) :: DeletedDocuments -> DeletedDocuments -> Bool # | |
| Show DeletedDocuments Source # | |
Defined in Database.Bloodhound.Client Methods showsPrec :: Int -> DeletedDocuments -> ShowS # show :: DeletedDocuments -> String # showList :: [DeletedDocuments] -> ShowS # | |
| FromJSON DeletedDocuments Source # | |
Defined in Database.Bloodhound.Client Methods parseJSON :: Value -> Parser DeletedDocuments # parseJSONList :: Value -> Parser [DeletedDocuments] # | |
data DeletedDocumentsRetries Source #
Constructors
| DeletedDocumentsRetries | |
Fields | |
Instances
| Eq DeletedDocumentsRetries Source # | |
Defined in Database.Bloodhound.Client Methods (==) :: DeletedDocumentsRetries -> DeletedDocumentsRetries -> Bool # (/=) :: DeletedDocumentsRetries -> DeletedDocumentsRetries -> Bool # | |
| Show DeletedDocumentsRetries Source # | |
Defined in Database.Bloodhound.Client Methods showsPrec :: Int -> DeletedDocumentsRetries -> ShowS # show :: DeletedDocumentsRetries -> String # showList :: [DeletedDocumentsRetries] -> ShowS # | |
| FromJSON DeletedDocumentsRetries Source # | |
Defined in Database.Bloodhound.Client Methods parseJSON :: Value -> Parser DeletedDocumentsRetries # parseJSONList :: Value -> Parser [DeletedDocumentsRetries] # | |
Searching
searchAll :: MonadBH m => Search -> m (BHResponse (SearchResult a)) Source #
searchByIndex :: MonadBH m => IndexName -> Search -> m (BHResponse (SearchResult a)) Source #
searchByIndex, given a Search and an IndexName, will perform that search
within an index on an Elasticsearch server.
>>>let query = TermQuery (Term "user" "bitemyapp") Nothing>>>let search = mkSearch (Just query) Nothing>>>response <- runBH' $ searchByIndex testIndex search
searchByIndices :: MonadBH m => NonEmpty IndexName -> Search -> m (BHResponse (SearchResult a)) Source #
searchByIndices is a variant of searchByIndex that executes a
Search over many indices. This is much faster than using
mapM to searchByIndex over a collection since it only
causes a single HTTP request to be emitted.
searchByIndexTemplate :: (FromJSON a, MonadBH m) => IndexName -> SearchTemplate -> m (BHResponse (SearchResult a)) Source #
searchByIndexTemplate, given a SearchTemplate and an IndexName, will perform that search
within an index on an Elasticsearch server.
>>>let query = SearchTemplateSource "{\"query\": { \"match\" : { \"{{my_field}}\" : \"{{my_value}}\" } }, \"size\" : \"{{my_size}}\"}">>>let search = mkSearchTemplate (Right query) Nothing>>>response <- runBH' $ searchByIndexTemplate testIndex search
searchByIndicesTemplate :: (FromJSON a, MonadBH m) => NonEmpty IndexName -> SearchTemplate -> m (BHResponse (SearchResult a)) Source #
searchByIndicesTemplate is a variant of searchByIndexTemplate that executes a
SearchTemplate over many indices. This is much faster than using
mapM to searchByIndexTemplate over a collection since it only
causes a single HTTP request to be emitted.
scanSearch :: (FromJSON a, MonadBH m, MonadThrow m) => IndexName -> Search -> m [Hit a] Source #
scanSearch uses the scroll API of elastic,
for a given IndexName. Note that this will
consume the entire search result set and will be doing O(n) list
appends so this may not be suitable for large result sets. In that
case, getInitialScroll and advanceScroll are good low level
tools. You should be able to hook them up trivially to conduit,
pipes, or your favorite streaming IO abstraction of choice. Note
that ordering on the search would destroy performance and thus is
ignored.
getInitialScroll :: (FromJSON a, MonadThrow m, MonadBH m) => IndexName -> Search -> m (ParsedEsResponse (SearchResult a)) Source #
For a given search, request a scroll for efficient streaming of
search results. Note that the search is put into SearchTypeScan
mode and thus results will not be sorted. Combine this with
advanceScroll to efficiently stream through the full result set
getInitialSortedScroll :: (FromJSON a, MonadThrow m, MonadBH m) => IndexName -> Search -> m (ParsedEsResponse (SearchResult a)) Source #
For a given search, request a scroll for efficient streaming of
search results. Combine this with advanceScroll to efficiently
stream through the full result set. Note that this search respects
sorting and may be less efficient than getInitialScroll.
Arguments
| :: (FromJSON a, MonadBH m, MonadThrow m) | |
| => ScrollId | |
| -> NominalDiffTime | How long should the snapshot of data be kept around? This timeout is updated every time |
| -> m (ParsedEsResponse (SearchResult a)) |
Use the given scroll to fetch the next page of documents. If there are no further pages, 'SearchResult.searchHits.hits' will be '[]'.
pitSearch :: (FromJSON a, MonadBH m, MonadThrow m, Show a) => IndexName -> Search -> m [Hit a] Source #
pitSearch uses the point in time (PIT) API of elastic, for a given
IndexName. Requires Elasticsearch >=7.10. Note that this will consume the
entire search result set and will be doing O(n) list appends so this may
not be suitable for large result sets. In that case, the point in time API
should be used directly with openPointInTime and closePointInTime.
Note that pitSearch utilizes the search_after parameter under the hood,
which requires a non-empty sortBody field in the provided Search value.
Otherwise, pitSearch will fail to return all matching documents.
For more information see https://www.elastic.co/guide/en/elasticsearch/reference/current/point-in-time-api.html.
openPointInTime :: (MonadBH m, MonadThrow m) => IndexName -> m (ParsedEsResponse OpenPointInTimeResponse) Source #
openPointInTime opens a point in time for an index given an IndexName.
Note that the point in time should be closed with closePointInTime as soon
as it is no longer needed.
For more information see https://www.elastic.co/guide/en/elasticsearch/reference/current/point-in-time-api.html.
closePointInTime :: (MonadBH m, MonadThrow m) => ClosePointInTime -> m (ParsedEsResponse ClosePointInTimeResponse) Source #
closePointInTime closes a point in time given a ClosePointInTime.
For more information see https://www.elastic.co/guide/en/elasticsearch/reference/current/point-in-time-api.html.
refreshIndex :: MonadBH m => IndexName -> m (BHResponse ShardResult) Source #
refreshIndex will force a refresh on an index. You must
do this if you want to read what you wrote.
>>>_ <- runBH' $ createIndex defaultIndexSettings testIndex>>>_ <- runBH' $ refreshIndex testIndex
mkSearch :: Maybe Query -> Maybe Filter -> Search Source #
mkSearch is a helper function for defaulting additional fields of a Search
to Nothing in case you only care about your Query and Filter. Use record update
syntax if you want to add things like aggregations or highlights while still using
this helper function.
>>>let query = TermQuery (Term "user" "bitemyapp") Nothing>>>mkSearch (Just query) NothingSearch {queryBody = Just (TermQuery (Term {termField = "user", termValue = "bitemyapp"}) Nothing), filterBody = Nothing, searchAfterKey = Nothing, sortBody = Nothing, aggBody = Nothing, highlight = Nothing, trackSortScores = False, from = From 0, size = Size 10, searchType = SearchTypeQueryThenFetch, fields = Nothing, source = Nothing}
mkAggregateSearch :: Maybe Query -> Aggregations -> Search Source #
mkAggregateSearch is a helper function that defaults everything in a Search except for
the Query and the Aggregation.
>>>let terms = TermsAgg $ (mkTermsAggregation "user") { termCollectMode = Just BreadthFirst }>>>termsTermsAgg (TermsAggregation {term = Left "user", termInclude = Nothing, termExclude = Nothing, termOrder = Nothing, termMinDocCount = Nothing, termSize = Nothing, termShardSize = Nothing, termCollectMode = Just BreadthFirst, termExecutionHint = Nothing, termAggs = Nothing})>>>let myAggregation = mkAggregateSearch Nothing $ mkAggregations "users" terms
mkHighlightSearch :: Maybe Query -> Highlights -> Search Source #
mkHighlightSearch is a helper function that defaults everything in a Search except for
the Query and the Aggregation.
>>>let query = QueryMatchQuery $ mkMatchQuery (FieldName "_all") (QueryString "haskell")>>>let testHighlight = Highlights Nothing [FieldHighlight (FieldName "message") Nothing]>>>let search = mkHighlightSearch (Just query) testHighlight
mkSearchTemplate :: Either SearchTemplateId SearchTemplateSource -> TemplateQueryKeyValuePairs -> SearchTemplate Source #
mkSearchTemplate is a helper function for defaulting additional fields of a SearchTemplate
to Nothing. Use record update syntax if you want to add things.
bulk :: MonadBH m => Vector BulkOperation -> m (BHResponse a) Source #
bulk uses
Elasticsearch's bulk API
to perform bulk operations. The BulkOperation data type encodes the
index/update/delete/create operations. You pass a Vector of BulkOperations
and a Server to bulk in order to send those operations up to your Elasticsearch
server to be performed. I changed from [BulkOperation] to a Vector due to memory overhead.
>>>let stream = V.fromList [BulkIndex testIndex (DocId "2") (toJSON (BulkTest "blah"))]>>>_ <- runBH' $ bulk stream>>>_ <- runBH' $ refreshIndex testIndex
Arguments
| :: From | The result offset |
| -> Size | The number of results to return |
| -> Search | The current seach |
| -> Search | The paged search |
pageSearch is a helper function that takes a search and assigns the from
and size fields for the search. The from parameter defines the offset
from the first result you want to fetch. The size parameter allows you to
configure the maximum amount of hits to be returned.
>>>let query = QueryMatchQuery $ mkMatchQuery (FieldName "_all") (QueryString "haskell")>>>let search = mkSearch (Just query) Nothing>>>searchSearch {queryBody = Just (QueryMatchQuery (MatchQuery {matchQueryField = FieldName "_all", matchQueryQueryString = QueryString "haskell", matchQueryOperator = Or, matchQueryZeroTerms = ZeroTermsNone, matchQueryCutoffFrequency = Nothing, matchQueryMatchType = Nothing, matchQueryAnalyzer = Nothing, matchQueryMaxExpansions = Nothing, matchQueryLenient = Nothing, matchQueryBoost = Nothing})), filterBody = Nothing, sortBody = Nothing, aggBody = Nothing, highlight = Nothing, trackSortScores = False, from = From 0, size = Size 10, searchType = SearchTypeQueryThenFetch, fields = Nothing, source = Nothing}>>>pageSearch (From 10) (Size 100) searchSearch {queryBody = Just (QueryMatchQuery (MatchQuery {matchQueryField = FieldName "_all", matchQueryQueryString = QueryString "haskell", matchQueryOperator = Or, matchQueryZeroTerms = ZeroTermsNone, matchQueryCutoffFrequency = Nothing, matchQueryMatchType = Nothing, matchQueryAnalyzer = Nothing, matchQueryMaxExpansions = Nothing, matchQueryLenient = Nothing, matchQueryBoost = Nothing})), filterBody = Nothing, sortBody = Nothing, aggBody = Nothing, highlight = Nothing, trackSortScores = False, from = From 10, size = Size 100, searchType = SearchTypeQueryThenFetch, fields = Nothing, source = Nothing}
mkShardCount :: Int -> Maybe ShardCount Source #
mkShardCount is a straight-forward smart constructor for ShardCount
which rejects Int values below 1 and above 1000.
>>>mkShardCount 10Just (ShardCount 10)
mkReplicaCount :: Int -> Maybe ReplicaCount Source #
mkReplicaCount is a straight-forward smart constructor for ReplicaCount
which rejects Int values below 0 and above 1000.
>>>mkReplicaCount 10Just (ReplicaCount 10)
Templates
storeSearchTemplate :: MonadBH m => SearchTemplateId -> SearchTemplateSource -> m (BHResponse Acknowledged) Source #
storeSearchTemplate, saves a SearchTemplateSource to be used later.
getSearchTemplate :: MonadBH m => SearchTemplateId -> m (BHResponse GetTemplateScript) Source #
getSearchTemplate, get info of an stored SearchTemplateSource.
deleteSearchTemplate :: MonadBH m => SearchTemplateId -> m (BHResponse Acknowledged) Source #
Snapshot/Restore
Snapshot Repos
getSnapshotRepos :: (MonadBH m, MonadThrow m) => SnapshotRepoSelection -> m (ParsedEsResponse [GenericSnapshotRepo]) Source #
getSnapshotRepos gets the definitions of a subset of the
defined snapshot repos.
Arguments
| :: (MonadBH m, SnapshotRepo repo) | |
| => SnapshotRepoUpdateSettings | Use |
| -> repo | |
| -> m (BHResponse Acknowledged) |
Create or update a snapshot repo
verifySnapshotRepo :: (MonadBH m, MonadThrow m) => SnapshotRepoName -> m (ParsedEsResponse SnapshotVerification) Source #
Verify if a snapshot repo is working. NOTE: this API did not make it into Elasticsearch until 1.4. If you use an older version, you will get an error here.
deleteSnapshotRepo :: MonadBH m => SnapshotRepoName -> m (BHResponse Acknowledged) Source #
Snapshots
createSnapshot :: MonadBH m => SnapshotRepoName -> SnapshotName -> SnapshotCreateSettings -> m (BHResponse Acknowledged) Source #
Create and start a snapshot
getSnapshots :: (MonadBH m, MonadThrow m) => SnapshotRepoName -> SnapshotSelection -> m (ParsedEsResponse [SnapshotInfo]) Source #
Get info about known snapshots given a pattern and repo name.
deleteSnapshot :: MonadBH m => SnapshotRepoName -> SnapshotName -> m (BHResponse Acknowledged) Source #
Delete a snapshot. Cancels if it is running.
Restoring Snapshots
Arguments
| :: MonadBH m | |
| => SnapshotRepoName | |
| -> SnapshotName | |
| -> SnapshotRestoreSettings | Start with |
| -> m (BHResponse Accepted) |
Restore a snapshot to the cluster See https://www.elastic.co/guide/en/elasticsearch/reference/1.7/modules-snapshots.html#_restore for more details.
Nodes
getNodesInfo :: (MonadBH m, MonadThrow m) => NodeSelection -> m (ParsedEsResponse NodesInfo) Source #
getNodesStats :: (MonadBH m, MonadThrow m) => NodeSelection -> m (ParsedEsResponse NodesStats) Source #
Request Utilities
encodeBulkOperations :: Vector BulkOperation -> ByteString Source #
encodeBulkOperations is a convenience function for dumping a vector of BulkOperation
into an ByteString
>>>let bulkOps = V.fromList [BulkIndex testIndex (DocId "2") (toJSON (BulkTest "blah"))]>>>encodeBulkOperations bulkOps"\n{\"index\":{\"_id\":\"2\",\"_index\":\"twitter\"}}\n{\"name\":\"blah\"}\n"
encodeBulkOperation :: BulkOperation -> ByteString Source #
encodeBulkOperation is a convenience function for dumping a single BulkOperation
into an ByteString
>>>let bulkOp = BulkIndex testIndex (DocId "2") (toJSON (BulkTest "blah"))>>>encodeBulkOperation bulkOp"{\"index\":{\"_id\":\"2\",\"_index\":\"twitter\"}}\n{\"name\":\"blah\"}"
Authentication
basicAuthHook :: Monad m => EsUsername -> EsPassword -> Request -> m Request Source #
This is a hook that can be set via the bhRequestHook function
that will authenticate all requests using an HTTP Basic
Authentication header. Note that it is *strongly* recommended that
this option only be used over an SSL connection.
> (mkBHEnv myServer myManager) { bhRequestHook = basicAuthHook (EsUsername "myuser") (EsPassword "mypass") }BHResponse-handling tools
isVersionConflict :: BHResponse a -> Bool Source #
Was there an optimistic concurrency control conflict when indexing a document?
isSuccess :: BHResponse a -> Bool Source #
Check '2xx' status codes
isCreated :: BHResponse a -> Bool Source #
Check '201' status code
parseEsResponse :: (MonadThrow m, FromJSON body) => BHResponse body -> m (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 body -> m parsed Source #
Parse BHResponse with an arbitrary parser
decodeResponse :: FromJSON a => BHResponse a -> Maybe a Source #
Helper around aeson decode
eitherDecodeResponse :: FromJSON a => BHResponse a -> Either String a Source #
Helper around aeson eitherDecode
Count
countByIndex :: (MonadBH m, MonadThrow m) => IndexName -> CountQuery -> m (ParsedEsResponse CountResponse) Source #
Generic
newtype Acknowledged Source #
Constructors
| Acknowledged | |
Fields | |
Instances
| Eq Acknowledged Source # | |
| Show Acknowledged Source # | |
Defined in Database.Bloodhound.Internal.Client.BHRequest Methods showsPrec :: Int -> Acknowledged -> ShowS # show :: Acknowledged -> String # showList :: [Acknowledged] -> ShowS # | |
| FromJSON Acknowledged Source # | |