Skip to content

Commit

Permalink
Start parsing
Browse files Browse the repository at this point in the history
  • Loading branch information
amitaibu committed Jul 24, 2024
1 parent e6093a7 commit b9f6b12
Show file tree
Hide file tree
Showing 2 changed files with 23 additions and 2 deletions.
24 changes: 22 additions & 2 deletions Application/Helper/Elasticsearch.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,15 @@
module Application.Helper.Elasticsearch where

import IHP.Prelude
import IHP.ModelSupport
import Database.Bloodhound
import Network.HTTP.Client (Manager, Response(..))
import Control.Lens ((^.))
import qualified Data.ByteString.Lazy as LBS
import Data.Aeson (ToJSON, FromJSON, Value, toJSON, parseJSON, withObject, (.:), decode, object, (.=), eitherDecode)
import IHP.ControllerSupport
import qualified Data.Text as T
import Prelude (read)

import Generated.Types

Expand Down Expand Up @@ -49,12 +51,30 @@ deleteIndexNews newsId = do
searchNews :: (?context :: ControllerContext) => Text -> IO [Id News]
searchNews queryText = do
-- Execute the search request
result <- runBH (mkBHEnv esServer esManager) $ searchByIndex indexName (mkSearch (Just query) Nothing)
response <- runBH (mkBHEnv esServer esManager) $ searchByIndex indexName (mkSearch (Just query) Nothing)
-- Parse the response
result <- parseEsResponse response
case result of
Left esError -> do
-- Handle the error (log it, return empty list, or throw an exception)
liftIO $ putStrLn $ "Error occurred: " ++ show esError
return []
Right (searchResult :: SearchResult Value) -> do
-- Extract the News IDs from the search result

let newsIds :: [Id News] = map (textToId . unDocId . hitDocId) $ hits $ searchHits searchResult
liftIO $ putStrLn $ "newsIds: " ++ show newsIds
return []

-- Parse result and extract the News ids. The News IDs is the Doc
pure []
where
(esServer, esManager) = getAppConfig @(Server, Manager)
indexName = IndexName "news"
query = QueryMatchQuery $ mkMatchQuery (FieldName "_all") (QueryString queryText)
-- @todo: Search all fields
query = QueryMatchQuery $ mkMatchQuery (FieldName "body") (QueryString queryText)

unDocId :: DocId -> Text
unDocId (DocId t) = t


1 change: 1 addition & 0 deletions Web/Controller/News.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ import Application.Helper.Elasticsearch
instance Controller NewsController where
action NewsAction = do
news <- query @News |> fetch
searchNews "bar"
render IndexView { .. }

action NewNewsAction = do
Expand Down

0 comments on commit b9f6b12

Please sign in to comment.