Commit 6b3ebf8d authored by Alexandre Delanoë's avatar Alexandre Delanoë

[API] Search, working on JSON instances (WIP)

parent a910c0de
Pipeline #988 failed with stage
......@@ -33,7 +33,7 @@ import Gargantext.API.Count (CountAPI, count, Query)
import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
import Gargantext.API.Node
import Gargantext.API.Prelude
import qualified Gargantext.API.Search as Search
-- import qualified Gargantext.API.Search as Search
import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node
......@@ -129,8 +129,8 @@ type GargPrivateAPI' =
:> CountAPI
-- Corpus endpoint --> TODO rename s/search/filter/g
:<|> "search" :> Capture "corpus" NodeId
:> (Search.API Search.SearchResult)
-- :<|> "search" :> Capture "corpus" NodeId
-- :> (Search.API Search.SearchResult)
-- TODO move to NodeAPI?
:<|> "graph" :> Summary "Graph endpoint"
......@@ -212,8 +212,8 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
:<|> count -- TODO: undefined
:<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
<$> PathNode <*> Search.api -- TODO: move elsewhere
-- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
-- <$> PathNode <*> Search.api -- TODO: move elsewhere
:<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
<$> PathNode <*> graphAPI uid -- TODO: mock
......
......@@ -36,17 +36,45 @@ import Servant
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
-----------------------------------------------------------------------
-- TODO-ACCESS: CanSearch? or is it part of CanGetNode
-- TODO-EVENTS: No event, this is a read-only query.
type API results = Summary "Search endpoint"
:> ReqBody '[JSON] SearchQuery
:> QueryParam "offset" Int
:> QueryParam "limit" Int
:> QueryParam "order" OrderBy
:> Post '[JSON] results
-----------------------------------------------------------------------
api :: NodeId -> GargServer (API SearchResult)
api nId (SearchQuery q SearchDoc) o l order =
SearchResultDoc <$> searchInCorpus nId False q o l order
api nId (SearchQuery q SearchContact) o l order = do
aIds <- isPairedWith NodeAnnuaire nId
-- TODO if paired with several corpus
case head aIds of
Nothing -> pure $ SearchNoResult "[G.A.Search] pair corpus with an Annuaire"
Just aId -> SearchResultContact <$> searchInCorpusWithContacts nId aId q o l order
-----------------------------------------------------------------------
-----------------------------------------------------------------------
-- | Main Types
-----------------------------------------------------------------------
data SearchType = SearchDoc | SearchContact
deriving (Generic)
instance FromJSON SearchType
{-
where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
-}
instance FromJSON SearchType where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
instance ToJSON SearchType
{-
where
toJSON = genericToJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
-}
instance ToJSON SearchType where
toJSON = genericToJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
instance ToSchema SearchType
instance Arbitrary SearchType where
arbitrary = elements [SearchDoc, SearchContact]
......@@ -57,14 +85,23 @@ data SearchQuery =
, expected :: !SearchType
} deriving (Generic)
instance FromJSON SearchQuery where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
instance FromJSON SearchQuery
{-
where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
-}
instance ToJSON SearchQuery where
toJSON = genericToJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
instance ToSchema SearchQuery where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
instance ToJSON SearchQuery
{-
where
toJSON = genericToJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
-}
instance ToSchema SearchQuery
{-
where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
-}
instance Arbitrary SearchQuery where
arbitrary = elements [SearchQuery ["electrodes"] SearchDoc]
......@@ -76,11 +113,17 @@ data SearchResult = SearchResultDoc { docs :: ![FacetDoc]}
deriving (Generic)
instance FromJSON SearchResult where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
instance FromJSON SearchResult
{-
where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
-}
instance ToJSON SearchResult where
toJSON = genericToJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
instance ToJSON SearchResult
{-
where
toJSON = genericToJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
-}
instance Arbitrary SearchResult where
arbitrary = do
......@@ -92,23 +135,4 @@ instance Arbitrary SearchResult where
instance ToSchema SearchResult where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "sr_")
-----------------------------------------------------------------------
-- TODO-ACCESS: CanSearch? or is it part of CanGetNode
-- TODO-EVENTS: No event, this is a read-only query.
type API results = Summary "Search endpoint"
:> ReqBody '[JSON] SearchQuery
:> QueryParam "offset" Int
:> QueryParam "limit" Int
:> QueryParam "order" OrderBy
:> Post '[JSON] results
-----------------------------------------------------------------------
api :: NodeId -> GargServer (API SearchResult)
api nId (SearchQuery q SearchDoc) o l order =
SearchResultDoc <$> searchInCorpus nId False q o l order
api nId (SearchQuery q SearchContact) o l order = do
aIds <- isPairedWith NodeAnnuaire nId
-- TODO if paired with several corpus
case head aIds of
Nothing -> pure $ SearchNoResult "[G.A.Search] pair corpus with an Annuaire"
Just aId -> SearchResultContact <$> searchInCorpusWithContacts nId aId q o l order
-----------------------------------------------------------------------
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