Commit 1303ec82 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[API][Search][Graph] type of Author with id.

parent 9bfcc0d8
...@@ -12,7 +12,6 @@ Count API part of Gargantext. ...@@ -12,7 +12,6 @@ Count API part of Gargantext.
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
...@@ -24,28 +23,21 @@ Count API part of Gargantext. ...@@ -24,28 +23,21 @@ Count API part of Gargantext.
module Gargantext.API.Search module Gargantext.API.Search
where where
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import Data.Aeson hiding (Error, fieldLabelModifier) import Data.Aeson hiding (Error, fieldLabelModifier)
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
import Data.Swagger import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import Database.PostgreSQL.Simple (Connection) import Database.PostgreSQL.Simple (Connection)
import Servant import Servant
import Test.QuickCheck.Arbitrary import Test.QuickCheck.Arbitrary
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
-- import Control.Applicative ((<*>)) -- import Control.Applicative ((<*>))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Database.TextSearch import Gargantext.Database.TextSearch
----------------------------------------------------------------------- -----------------------------------------------------------------------
data SearchQuery = SearchQuery { sq_query :: [Text] data SearchQuery = SearchQuery { sq_query :: [Text]
, sq_parent_id :: Int , sq_parent_id :: Int
...@@ -56,19 +48,34 @@ instance ToSchema SearchQuery where ...@@ -56,19 +48,34 @@ instance ToSchema SearchQuery where
genericDeclareNamedSchema genericDeclareNamedSchema
defaultSchemaOptions {fieldLabelModifier = \fieldLabel -> drop 3 fieldLabel} defaultSchemaOptions {fieldLabelModifier = \fieldLabel -> drop 3 fieldLabel}
instance Arbitrary SearchQuery where instance Arbitrary SearchQuery where
arbitrary = elements [SearchQuery ["electrodes"] 472764] arbitrary = elements [SearchQuery ["electrodes"] 472764]
----------------------------------------------------------------------- -----------------------------------------------------------------------
data Author = Author { _a_name :: Text
, _a_id :: Int
} deriving (Generic)
$(deriveJSON (unPrefix "_a_") ''Author)
instance ToSchema Author where
declareNamedSchema =
genericDeclareNamedSchema
defaultSchemaOptions {fieldLabelModifier = \fieldLabel -> drop 3 fieldLabel}
arbitraryAuthor :: Author
arbitraryAuthor = Author "Jezequel" 1011669
instance Arbitrary Author where
arbitrary = elements [arbitraryAuthor]
-----------------------------------------------------------------------
data SearchResult = SearchResult { sr_id :: Int data SearchResult = SearchResult { sr_id :: Int
, sr_title :: Text , sr_title :: Text
, sr_authors :: Text , sr_authors :: [Author]
} deriving (Generic) } deriving (Generic)
$(deriveJSON (unPrefix "sr_") ''SearchResult) $(deriveJSON (unPrefix "sr_") ''SearchResult)
instance Arbitrary SearchResult where instance Arbitrary SearchResult where
arbitrary = elements [SearchResult 1 "Title" "Authors"] arbitrary = elements [SearchResult 1 "Title" [arbitraryAuthor]]
instance ToSchema SearchResult where instance ToSchema SearchResult where
declareNamedSchema = declareNamedSchema =
...@@ -97,7 +104,7 @@ type SearchAPI = Post '[JSON] SearchResults ...@@ -97,7 +104,7 @@ type SearchAPI = Post '[JSON] SearchResults
search :: Connection -> SearchQuery -> Handler SearchResults search :: Connection -> SearchQuery -> Handler SearchResults
search c (SearchQuery q pId) = search c (SearchQuery q pId) =
liftIO $ SearchResults <$> map (\(i, _, t, _, a, _) -> SearchResult i (cs $ encode t) (cs $ encode a)) liftIO $ SearchResults <$> map (\(i, _, t, _, a, _) -> SearchResult i (cs $ encode t) [arbitraryAuthor])
<$> textSearch c (toTSQuery q) pId 5 0 Desc <$> textSearch c (toTSQuery q) pId 5 0 Desc
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