Commit 314ed198 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[API/REFACT] search doc | contact

parent 4d0b27ac
...@@ -41,7 +41,6 @@ import Gargantext.API.Metrics ...@@ -41,7 +41,6 @@ import Gargantext.API.Metrics
import Gargantext.API.Ngrams (TabType(..), TableNgramsApi, apiNgramsTableCorpus) import Gargantext.API.Ngrams (TabType(..), TableNgramsApi, apiNgramsTableCorpus)
import Gargantext.API.Node.New import Gargantext.API.Node.New
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.API.Search (SearchDocsAPI, searchDocs, SearchPairsAPI, searchPairs)
import Gargantext.API.Table import Gargantext.API.Table
import Gargantext.Core.Types (NodeTableResult) import Gargantext.Core.Types (NodeTableResult)
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
...@@ -66,6 +65,7 @@ import Test.QuickCheck (elements) ...@@ -66,6 +65,7 @@ import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary) import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import qualified Gargantext.API.Node.Share as Share import qualified Gargantext.API.Node.Share as Share
import qualified Gargantext.API.Node.Update as Update import qualified Gargantext.API.Node.Update as Update
import qualified Gargantext.API.Search as Search
import qualified Gargantext.Database.Action.Delete as Action (deleteNode) import qualified Gargantext.Database.Action.Delete as Action (deleteNode)
import qualified Gargantext.Database.Query.Table.Node.Update as U (update, Update(..)) import qualified Gargantext.Database.Query.Table.Node.Update as U (update, Update(..))
...@@ -129,14 +129,13 @@ type NodeAPI a = Get '[JSON] (Node a) ...@@ -129,14 +129,13 @@ type NodeAPI a = Get '[JSON] (Node a)
:<|> "ngrams" :> TableNgramsApi :<|> "ngrams" :> TableNgramsApi
:<|> "category" :> CatApi :<|> "category" :> CatApi
:<|> "search" :> SearchDocsAPI :<|> "search" :> (Search.API Search.SearchResult)
:<|> "share" :> Share.API :<|> "share" :> Share.API
-- Pairing utilities -- Pairing utilities
:<|> "pairwith" :> PairWith :<|> "pairwith" :> PairWith
:<|> "pairs" :> Pairs :<|> "pairs" :> Pairs
:<|> "pairing" :> PairingApi :<|> "pairing" :> PairingApi
:<|> "searchPair" :> SearchPairsAPI
-- VIZ -- VIZ
:<|> "metrics" :> ScatterAPI :<|> "metrics" :> ScatterAPI
...@@ -206,13 +205,12 @@ nodeAPI p uId id' = withAccess (Proxy :: Proxy (NodeAPI a)) Proxy uId (PathNode ...@@ -206,13 +205,12 @@ nodeAPI p uId id' = withAccess (Proxy :: Proxy (NodeAPI a)) Proxy uId (PathNode
:<|> apiNgramsTableCorpus id' :<|> apiNgramsTableCorpus id'
:<|> catApi id' :<|> catApi id'
:<|> searchDocs id' :<|> Search.api id'
:<|> Share.api id' :<|> Share.api id'
-- Pairing Tools -- Pairing Tools
:<|> pairWith id' :<|> pairWith id'
:<|> pairs id' :<|> pairs id'
:<|> getPair id' :<|> getPair id'
:<|> searchPairs id'
:<|> scatterApi id' :<|> scatterApi id'
:<|> chartApi id' :<|> chartApi id'
......
...@@ -33,7 +33,7 @@ import Gargantext.API.Count (CountAPI, count, Query) ...@@ -33,7 +33,7 @@ import Gargantext.API.Count (CountAPI, count, Query)
import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc) import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
import Gargantext.API.Node import Gargantext.API.Node
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.API.Search (SearchPairsAPI, searchPairs) import qualified Gargantext.API.Search as Search
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Admin.Types.Hyperdata import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
...@@ -130,7 +130,7 @@ type GargPrivateAPI' = ...@@ -130,7 +130,7 @@ type GargPrivateAPI' =
-- Corpus endpoint --> TODO rename s/search/filter/g -- Corpus endpoint --> TODO rename s/search/filter/g
:<|> "search" :> Capture "corpus" NodeId :<|> "search" :> Capture "corpus" NodeId
:> SearchPairsAPI :> (Search.API Search.SearchResult)
-- TODO move to NodeAPI? -- TODO move to NodeAPI?
:<|> "graph" :> Summary "Graph endpoint" :<|> "graph" :> Summary "Graph endpoint"
...@@ -212,8 +212,8 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid)) ...@@ -212,8 +212,8 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
:<|> count -- TODO: undefined :<|> count -- TODO: undefined
:<|> withAccess (Proxy :: Proxy SearchPairsAPI) Proxy uid :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
<$> PathNode <*> searchPairs -- TODO: move elsewhere <$> PathNode <*> Search.api -- TODO: move elsewhere
:<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
<$> PathNode <*> graphAPI uid -- TODO: mock <$> PathNode <*> graphAPI uid -- TODO: mock
......
...@@ -35,9 +35,19 @@ import Servant ...@@ -35,9 +35,19 @@ import Servant
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary import Test.QuickCheck.Arbitrary
-----------------------------------------------------------------------
data SearchType = SearchDoc | SearchContact
deriving (Generic)
$(deriveJSON (unPrefix "") ''SearchType)
instance ToSchema SearchType
instance Arbitrary SearchType where
arbitrary = elements [SearchDoc, SearchContact]
----------------------------------------------------------------------- -----------------------------------------------------------------------
data SearchQuery = SearchQuery data SearchQuery = SearchQuery
{ sq_query :: [Text] { sq_query :: [Text]
, sq_type :: SearchType
} deriving (Generic) } deriving (Generic)
$(deriveJSON (unPrefix "sq_") ''SearchQuery) $(deriveJSON (unPrefix "sq_") ''SearchQuery)
...@@ -46,56 +56,39 @@ instance ToSchema SearchQuery where ...@@ -46,56 +56,39 @@ instance ToSchema SearchQuery where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "sq_") declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "sq_")
instance Arbitrary SearchQuery where instance Arbitrary SearchQuery where
arbitrary = elements [SearchQuery ["electrodes"]] arbitrary = elements [SearchQuery ["electrodes"] SearchDoc]
----------------------------------------------------------------------- -----------------------------------------------------------------------
data SearchResult = SearchResultDoc { sr_result :: [FacetDoc]}
| SearchResultContact { sr_results :: [FacetPaired Int UTCTime HyperdataContact Int] } | SearchNoResult { sr_message :: Text }
deriving (Generic)
$(deriveJSON (unPrefix "sr_") ''SearchResult)
instance Arbitrary SearchResult where
arbitrary = do
srd <- SearchResultDoc <$> arbitrary
src <- SearchResultContact <$> arbitrary
srn <- pure $ SearchNoResult "No result because.."
elements [srd, src, srn]
instance ToSchema SearchResult where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "sr_")
----------------------------------------------------------------------- -----------------------------------------------------------------------
-- TODO-ACCESS: CanSearch? or is it part of CanGetNode -- TODO-ACCESS: CanSearch? or is it part of CanGetNode
-- TODO-EVENTS: No event, this is a read-only query. -- TODO-EVENTS: No event, this is a read-only query.
type SearchAPI results = Summary "Search endpoint" type API results = Summary "Search endpoint"
:> ReqBody '[JSON] SearchQuery :> ReqBody '[JSON] SearchQuery
:> QueryParam "offset" Int :> QueryParam "offset" Int
:> QueryParam "limit" Int :> QueryParam "limit" Int
:> QueryParam "order" OrderBy :> QueryParam "order" OrderBy
:> Post '[JSON] results :> Post '[JSON] results
type SearchDocsAPI = SearchAPI SearchDocResults
searchDocs :: NodeId -> GargServer SearchDocsAPI
searchDocs nId (SearchQuery q) o l order =
SearchDocResults <$> searchInCorpus nId False q o l order
--SearchResults <$> searchInCorpusWithContacts nId q o l order
data SearchDocResults = SearchDocResults { sdr_results :: [FacetDoc]}
deriving (Generic)
$(deriveJSON (unPrefix "sdr_") ''SearchDocResults)
instance Arbitrary SearchDocResults where
arbitrary = SearchDocResults <$> arbitrary
instance ToSchema SearchDocResults where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "sdr_")
----------------------------------------------------------------------- -----------------------------------------------------------------------
type SearchPairsAPI = Summary "" api :: NodeId -> GargServer (API SearchResult)
:> "list" api nId (SearchQuery q SearchDoc) o l order =
:> Capture "annuaire" AnnuaireId SearchResultDoc <$> searchInCorpus nId False q o l order
:> SearchAPI SearchPairedResults api nId (SearchQuery q SearchContact) o l order =
searchPairs :: NodeId -> GargServer SearchPairsAPI -- SearchPairedResults <$> searchInCorpusWithContacts pId aId q o l order
searchPairs pId aId (SearchQuery q) o l order = pure $ SearchNoResult "Need Implementation"
SearchPairedResults <$> searchInCorpusWithContacts pId aId q o l order
data SearchPairedResults =
SearchPairedResults { spr_results :: [FacetPaired Int UTCTime HyperdataContact Int] }
deriving (Generic)
$(deriveJSON (unPrefix "spr_") ''SearchPairedResults)
instance Arbitrary SearchPairedResults where
arbitrary = SearchPairedResults <$> arbitrary
instance ToSchema SearchPairedResults where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "spr_")
----------------------------------------------------------------------- -----------------------------------------------------------------------
...@@ -65,7 +65,6 @@ isPairedWith nt nId = runOpaQuery (selectQuery nt nId) ...@@ -65,7 +65,6 @@ isPairedWith nt nId = runOpaQuery (selectQuery nt nId)
where where
cond (node, node_node) = node^.node_id .== node_node^. nn_node2_id cond (node, node_node) = node^.node_id .== node_node^. nn_node2_id
----------------------------------------------------------------------- -----------------------------------------------------------------------
pairing :: AnnuaireId -> CorpusId -> Maybe ListId -> GargNoServer Int pairing :: AnnuaireId -> CorpusId -> Maybe ListId -> GargNoServer Int
pairing a c l' = do pairing a c l' = do
......
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