Add search after functionality

This commit is contained in:
Shulhi Sapli 2018-07-31 14:53:33 +08:00
parent 2916540264
commit 4967c62843
3 changed files with 25 additions and 18 deletions

View File

@ -523,13 +523,13 @@ createIndex indexSettings (IndexName indexName) =
createIndexWith :: MonadBH m createIndexWith :: MonadBH m
=> [UpdatableIndexSetting] => [UpdatableIndexSetting]
-> Int -- ^ shard count -> Int -- ^ shard count
-> IndexName -> IndexName
-> m Reply -> m Reply
createIndexWith updates shards (IndexName indexName) = createIndexWith updates shards (IndexName indexName) =
bindM2 put url (return (Just body)) bindM2 put url (return (Just body))
where url = joinPath [indexName] where url = joinPath [indexName]
body = encode $ object body = encode $ object
["settings" .= deepMerge ["settings" .= deepMerge
( HM.singleton "index.number_of_shards" (toJSON shards) : ( HM.singleton "index.number_of_shards" (toJSON shards) :
[u | Object u <- toJSON <$> updates] [u | Object u <- toJSON <$> updates]
) )
@ -575,8 +575,8 @@ getIndexSettings (IndexName indexName) =
where where
url = joinPath [indexName, "_settings"] url = joinPath [indexName, "_settings"]
-- | 'forceMergeIndex' -- | 'forceMergeIndex'
-- --
-- The force merge API allows to force merging of one or more indices through -- 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 -- 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 -- within each shard. The force merge operation allows to reduce the number of
@ -1035,10 +1035,10 @@ searchByType (IndexName indexName)
-- search results. Note that the search is put into 'SearchTypeScan' -- search results. Note that the search is put into 'SearchTypeScan'
-- mode and thus results will not be sorted. Combine this with -- mode and thus results will not be sorted. Combine this with
-- 'advanceScroll' to efficiently stream through the full result set -- 'advanceScroll' to efficiently stream through the full result set
getInitialScroll :: getInitialScroll ::
(FromJSON a, MonadThrow m, MonadBH m) => IndexName -> (FromJSON a, MonadThrow m, MonadBH m) => IndexName ->
MappingName -> MappingName ->
Search -> Search ->
m (Either EsError (SearchResult a)) m (Either EsError (SearchResult a))
getInitialScroll (IndexName indexName) (MappingName mappingName) search' = do getInitialScroll (IndexName indexName) (MappingName mappingName) search' = do
let url = addQuery params <$> joinPath [indexName, mappingName, "_search"] let url = addQuery params <$> joinPath [indexName, mappingName, "_search"]
@ -1063,7 +1063,7 @@ getInitialSortedScroll (IndexName indexName) (MappingName mappingName) search =
resp' <- bindM2 dispatchSearch url (return search) resp' <- bindM2 dispatchSearch url (return search)
parseEsResponse resp' parseEsResponse resp'
scroll' :: (FromJSON a, MonadBH m, MonadThrow m) => Maybe ScrollId -> scroll' :: (FromJSON a, MonadBH m, MonadThrow m) => Maybe ScrollId ->
m ([Hit a], Maybe ScrollId) m ([Hit a], Maybe ScrollId)
scroll' Nothing = return ([], Nothing) scroll' Nothing = return ([], Nothing)
scroll' (Just sid) = do scroll' (Just sid) = do
@ -1090,13 +1090,13 @@ advanceScroll (ScrollId sid) scroll = do
where scrollTime = showText secs <> "s" where scrollTime = showText secs <> "s"
secs :: Integer secs :: Integer
secs = round scroll secs = round scroll
scrollObject = object [ "scroll" .= scrollTime scrollObject = object [ "scroll" .= scrollTime
, "scroll_id" .= sid , "scroll_id" .= sid
] ]
simpleAccumulator :: simpleAccumulator ::
(FromJSON a, MonadBH m, MonadThrow m) => (FromJSON a, MonadBH m, MonadThrow m) =>
[Hit a] -> [Hit a] ->
([Hit a], Maybe ScrollId) -> ([Hit a], Maybe ScrollId) ->
m ([Hit a], Maybe ScrollId) m ([Hit a], Maybe ScrollId)
@ -1134,9 +1134,9 @@ scanSearch indexName mappingName search = do
-- --
-- >>> let query = TermQuery (Term "user" "bitemyapp") Nothing -- >>> let query = TermQuery (Term "user" "bitemyapp") Nothing
-- >>> mkSearch (Just query) Nothing -- >>> mkSearch (Just query) Nothing
-- Search {queryBody = Just (TermQuery (Term {termField = "user", termValue = "bitemyapp"}) Nothing), filterBody = Nothing, sortBody = Nothing, aggBody = Nothing, highlight = Nothing, trackSortScores = False, from = From 0, size = Size 10, searchType = SearchTypeQueryThenFetch, fields = Nothing, source = Nothing} -- Search {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}
mkSearch :: Maybe Query -> Maybe Filter -> Search mkSearch :: Maybe Query -> Maybe Filter -> Search
mkSearch query filter = Search query filter Nothing Nothing Nothing False (From 0) (Size 10) SearchTypeQueryThenFetch Nothing Nothing Nothing Nothing mkSearch query filter = Search query filter Nothing Nothing Nothing False (From 0) (Size 10) SearchTypeQueryThenFetch Nothing Nothing Nothing Nothing Nothing
-- | 'mkAggregateSearch' is a helper function that defaults everything in a 'Search' except for -- | 'mkAggregateSearch' is a helper function that defaults everything in a 'Search' except for
-- the 'Query' and the 'Aggregation'. -- the 'Query' and the 'Aggregation'.
@ -1146,7 +1146,7 @@ mkSearch query filter = Search query filter Nothing Nothing Nothing False (From
-- TermsAgg (TermsAggregation {term = Left "user", termInclude = Nothing, termExclude = Nothing, termOrder = Nothing, termMinDocCount = Nothing, termSize = Nothing, termShardSize = Nothing, termCollectMode = Just BreadthFirst, termExecutionHint = Nothing, termAggs = Nothing}) -- TermsAgg (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 -- >>> let myAggregation = mkAggregateSearch Nothing $ mkAggregations "users" terms
mkAggregateSearch :: Maybe Query -> Aggregations -> Search mkAggregateSearch :: Maybe Query -> Aggregations -> Search
mkAggregateSearch query mkSearchAggs = Search query Nothing Nothing (Just mkSearchAggs) Nothing False (From 0) (Size 0) SearchTypeQueryThenFetch Nothing Nothing Nothing Nothing mkAggregateSearch query mkSearchAggs = Search query Nothing Nothing (Just mkSearchAggs) Nothing False (From 0) (Size 0) SearchTypeQueryThenFetch Nothing Nothing Nothing Nothing Nothing
-- | 'mkHighlightSearch' is a helper function that defaults everything in a 'Search' except for -- | 'mkHighlightSearch' is a helper function that defaults everything in a 'Search' except for
-- the 'Query' and the 'Aggregation'. -- the 'Query' and the 'Aggregation'.
@ -1155,7 +1155,7 @@ mkAggregateSearch query mkSearchAggs = Search query Nothing Nothing (Just mkSear
-- >>> let testHighlight = Highlights Nothing [FieldHighlight (FieldName "message") Nothing] -- >>> let testHighlight = Highlights Nothing [FieldHighlight (FieldName "message") Nothing]
-- >>> let search = mkHighlightSearch (Just query) testHighlight -- >>> let search = mkHighlightSearch (Just query) testHighlight
mkHighlightSearch :: Maybe Query -> Highlights -> Search mkHighlightSearch :: Maybe Query -> Highlights -> Search
mkHighlightSearch query searchHighlights = Search query Nothing Nothing Nothing (Just searchHighlights) False (From 0) (Size 10) SearchTypeQueryThenFetch Nothing Nothing Nothing Nothing mkHighlightSearch query searchHighlights = Search query Nothing Nothing Nothing (Just searchHighlights) False (From 0) (Size 10) SearchTypeQueryThenFetch Nothing Nothing Nothing Nothing Nothing
-- | 'pageSearch' is a helper function that takes a search and assigns the from -- | '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 -- and size fields for the search. The from parameter defines the offset

View File

@ -6,6 +6,7 @@ module Database.V5.Bloodhound.Internal.Aggregation where
import Bloodhound.Import import Bloodhound.Import
import qualified Data.Aeson as Aeson
import qualified Data.HashMap.Strict as HM import qualified Data.HashMap.Strict as HM
import qualified Data.Map.Strict as M import qualified Data.Map.Strict as M
import qualified Data.Text as T import qualified Data.Text as T
@ -445,6 +446,7 @@ instance Monoid (SearchHits a) where
mempty = SearchHits 0 Nothing mempty mempty = SearchHits 0 Nothing mempty
mappend = (<>) mappend = (<>)
type SearchAfterKey = [Aeson.Value]
data Hit a = data Hit a =
Hit { hitIndex :: IndexName Hit { hitIndex :: IndexName
@ -452,6 +454,7 @@ data Hit a =
, hitDocId :: DocId , hitDocId :: DocId
, hitScore :: Score , hitScore :: Score
, hitSource :: Maybe a , hitSource :: Maybe a
, hitSort :: Maybe SearchAfterKey
, hitFields :: Maybe HitFields , hitFields :: Maybe HitFields
, hitHighlight :: Maybe HitHighlight } deriving (Eq, Show) , hitHighlight :: Maybe HitHighlight } deriving (Eq, Show)
@ -462,6 +465,7 @@ instance (FromJSON a) => FromJSON (Hit a) where
v .: "_id" <*> v .: "_id" <*>
v .: "_score" <*> v .: "_score" <*>
v .:? "_source" <*> v .:? "_source" <*>
v .:? "sort" <*>
v .:? "fields" <*> v .:? "fields" <*>
v .:? "highlight" v .:? "highlight"
parseJSON _ = empty parseJSON _ = empty

View File

@ -382,6 +382,7 @@ module Database.V5.Bloodhound.Types
, DateMathUnit(..) , DateMathUnit(..)
, TopHitsAggregation(..) , TopHitsAggregation(..)
, StatisticsAggregation(..) , StatisticsAggregation(..)
, SearchAfterKey
, Highlights(..) , Highlights(..)
, FieldHighlight(..) , FieldHighlight(..)
@ -413,7 +414,7 @@ module Database.V5.Bloodhound.Types
, TokenChar(..) , TokenChar(..)
, Shingle(..) , Shingle(..)
, Language(..) , Language(..)
) where ) where
import Bloodhound.Import import Bloodhound.Import
@ -444,6 +445,7 @@ data Search = Search { queryBody :: Maybe Query
, from :: From , from :: From
, size :: Size , size :: Size
, searchType :: SearchType , searchType :: SearchType
, searchAfterKey :: Maybe SearchAfterKey
, fields :: Maybe [FieldName] , fields :: Maybe [FieldName]
, scriptFields :: Maybe ScriptFields , scriptFields :: Maybe ScriptFields
, source :: Maybe Source , source :: Maybe Source
@ -453,7 +455,7 @@ data Search = Search { queryBody :: Maybe Query
instance ToJSON Search where instance ToJSON Search where
toJSON (Search mquery sFilter sort searchAggs toJSON (Search mquery sFilter sort searchAggs
highlight sTrackSortScores sFrom sSize _ sFields highlight sTrackSortScores sFrom sSize _ sAfter sFields
sScriptFields sSource sSuggest) = sScriptFields sSource sSuggest) =
omitNulls [ "query" .= query' omitNulls [ "query" .= query'
, "sort" .= sort , "sort" .= sort
@ -462,6 +464,7 @@ instance ToJSON Search where
, "from" .= sFrom , "from" .= sFrom
, "size" .= sSize , "size" .= sSize
, "track_scores" .= sTrackSortScores , "track_scores" .= sTrackSortScores
, "search_after" .= sAfter
, "fields" .= sFields , "fields" .= sFields
, "script_fields" .= sScriptFields , "script_fields" .= sScriptFields
, "_source" .= sSource , "_source" .= sSource