Commit ec633d46 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] TEXT SEARCH API done (can be adapted for annuaire).

parent 13fab086
......@@ -68,7 +68,8 @@ import Gargantext.API.Node ( Roots , roots
, NodeAPI , nodeAPI
, NodesAPI , nodesAPI
)
import Gargantext.API.Count ( CountAPI, count, Query)
import Gargantext.API.Count ( CountAPI, count, Query)
import Gargantext.API.Search ( SearchAPI, search, SearchQuery)
import Gargantext.API.Orchestrator
import Gargantext.API.Orchestrator.Types
......@@ -199,7 +200,10 @@ type GargAPI = "user" :> Summary "First user endpoint"
-- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
:<|> "count" :> Summary "Count endpoint"
:> ReqBody '[JSON] Query :> CountAPI
:> ReqBody '[JSON] Query :> CountAPI
:<|> "search":> Summary "Search endpoint"
:> ReqBody '[JSON] SearchQuery :> SearchAPI
-- :<|> "scraper" :> WithCallbacks ScraperAPI
......@@ -226,6 +230,7 @@ server env = do
:<|> nodeAPI conn
:<|> nodesAPI conn
:<|> count
:<|> search conn
-- :<|> orchestrator
where
conn = env ^. env_conn
......
......@@ -63,7 +63,6 @@ instance Arbitrary Scraper where
instance ToSchema Scraper
-----------------------------------------------------------------------
data QueryBool = QueryBool Text
deriving (Eq, Show, Generic)
......@@ -135,7 +134,6 @@ instance Arbitrary Counts where
instance ToSchema Counts
-----------------------------------------------------------------------
data Count = Count { count_name :: Scraper
, count_count :: Maybe Int
......
{-|
Module : Gargantext.API.Count
Description : Server API
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Count API part of Gargantext.
-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.API.Search
where
import GHC.Generics (Generic)
import Control.Monad.IO.Class (liftIO)
import Prelude (Bounded, Enum, minBound, maxBound)
import Data.Aeson hiding (Error, fieldLabelModifier)
import Data.Aeson.TH (deriveJSON)
import Data.Eq (Eq())
import Data.Either
import Data.List (repeat, permutations)
import Data.Swagger
import Data.Swagger.SchemaOptions
import Data.Text (Text, pack)
import Database.PostgreSQL.Simple (Connection)
import Servant
import Test.QuickCheck.Arbitrary
import Test.QuickCheck (elements)
-- import Control.Applicative ((<*>))
import Gargantext.Prelude
import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Database.TextSearch
-----------------------------------------------------------------------
data SearchQuery = SearchQuery { sq_query :: [Text]
, sq_parent_id :: Int
} deriving (Generic)
$(deriveJSON (unPrefix "sq_") ''SearchQuery)
instance ToSchema SearchQuery where
declareNamedSchema =
genericDeclareNamedSchema
defaultSchemaOptions {fieldLabelModifier = \fieldLabel -> drop 3 fieldLabel}
instance Arbitrary SearchQuery where
arbitrary = elements [SearchQuery ["query"] 1]
-----------------------------------------------------------------------
data SearchResult = SearchResult { sr_id :: Int
, sr_name :: Text
} deriving (Generic)
$(deriveJSON (unPrefix "sr_") ''SearchResult)
instance Arbitrary SearchResult where
arbitrary = elements [SearchResult 1 "name"]
instance ToSchema SearchResult where
declareNamedSchema =
genericDeclareNamedSchema
defaultSchemaOptions {fieldLabelModifier = \fieldLabel -> drop 3 fieldLabel}
-----------------------------------------------------------------------
data SearchResults = SearchResults { srs_results :: [SearchResult]}
deriving (Generic)
$(deriveJSON (unPrefix "srs_") ''SearchResults)
instance Arbitrary SearchResults where
arbitrary = SearchResults <$> arbitrary
instance ToSchema SearchResults where
declareNamedSchema =
genericDeclareNamedSchema
defaultSchemaOptions {fieldLabelModifier = \fieldLabel -> drop 4 fieldLabel}
-----------------------------------------------------------------------
type SearchAPI = Post '[JSON] SearchResults
-----------------------------------------------------------------------
search :: Connection -> SearchQuery -> Handler SearchResults
search c (SearchQuery q pId) =
liftIO $ SearchResults <$> map (\(i, y, t, s, _) -> SearchResult i (cs $ encode t))
<$> textSearch c (toTSQuery q) pId 5 0 Desc
......@@ -33,6 +33,9 @@ import Gargantext.Prelude
newtype TSQuery = UnsafeTSQuery [Text]
toTSQuery :: [Text] -> TSQuery
toTSQuery txt = UnsafeTSQuery txt
instance IsString TSQuery
where
fromString = UnsafeTSQuery . words . cs
......@@ -63,7 +66,7 @@ instance ToField Order
-- ADD ngrams count
-- TESTS
textSearchQuery :: Query
textSearchQuery = "SELECT n.id, n.hyperdata->'publication_date' \
textSearchQuery = "SELECT n.id, n.hyperdata->'publication_year' \
\ , n.hyperdata->'title' \
\ , n.hyperdata->'source' \
\ , COALESCE(nn.score,null) \
......@@ -71,7 +74,7 @@ textSearchQuery = "SELECT n.id, n.hyperdata->'publication_date' \
\ LEFT JOIN nodes_nodes nn ON nn.node2_id = n.id \
\ WHERE \
\ n.title_abstract @@ (?::tsquery) \
\ AND n.parent_id = ? AND n.typename = 4 \
\ AND n.parent_id = ? AND n.typename = 40 \
\ ORDER BY n.hyperdata -> 'publication_date' ? \
\ offset ? limit ?;"
......@@ -82,7 +85,7 @@ textSearch :: Connection
-> IO [(Int,Value,Value,Value, Maybe Int)]
textSearch conn q p l o ord = query conn textSearchQuery (q,p,ord, o,l)
textSearchTest :: TSQuery -> IO ()
textSearchTest q = connectGargandb "gargantext.ini"
>>= \conn -> textSearch conn q 421968 10 0 Asc
textSearchTest :: ParentId -> TSQuery -> IO ()
textSearchTest pId q = connectGargandb "gargantext.ini"
>>= \conn -> textSearch conn q pId 5 0 Asc
>>= mapM_ print
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment