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

[SearchIn] Corpus API route : corpus/{id}/search

parent 34fbf078
......@@ -58,6 +58,7 @@ import qualified Gargantext.Database.Node.Update as U (update, Update(..))
import Gargantext.Database.Facet (FacetDoc , runViewDocuments', OrderBy(..),FacetChart,runViewAuthorsDoc)
import Gargantext.Database.Tree (treeDB, HasTreeError(..), TreeError(..))
import Gargantext.Database.Schema.NodeNode (nodesToFavorite, nodesToTrash)
import Gargantext.API.Search ( SearchAPI, searchIn, SearchInQuery)
-- Graph
--import Gargantext.Text.Flow
import Gargantext.Viz.Graph hiding (Node)-- (Graph(_graph_metadata),LegendField(..), GraphMetadata(..),readGraphFromJson,defaultGraph)
......@@ -113,6 +114,12 @@ type NodeAPI a = Get '[JSON] (Node a)
:<|> "chart" :> ChartApi
:<|> "favorites" :> FavApi
:<|> "documents" :> DocsApi
:<|> "search":> Summary "Node Search"
:> ReqBody '[JSON] SearchInQuery
:> QueryParam "offset" Int
:> QueryParam "limit" Int
:> QueryParam "order" OrderBy
:> SearchAPI
type RenameApi = Summary " RenameNode Node"
:> ReqBody '[JSON] RenameNode
......@@ -147,6 +154,8 @@ nodeAPI conn p id
:<|> getChart conn id
:<|> favApi conn id
:<|> delDocs conn id
:<|> searchIn conn id
-- Annuaire
-- :<|> upload
-- :<|> query
......
......@@ -42,6 +42,8 @@ import Gargantext.Database.TextSearch
import Gargantext.Database.Facet
-----------------------------------------------------------------------
-- | SearchIn [NodesId] if empty then global search
-- TODO [Int]
data SearchQuery = SearchQuery { sq_query :: [Text]
, sq_corpus_id :: Int
} deriving (Generic)
......@@ -54,6 +56,20 @@ instance ToSchema SearchQuery where
instance Arbitrary SearchQuery where
arbitrary = elements [SearchQuery ["electrodes"] 472764]
--
data SearchInQuery = SearchInQuery { siq_query :: [Text]
} deriving (Generic)
$(deriveJSON (unPrefix "siq_") ''SearchInQuery)
instance ToSchema SearchInQuery where
declareNamedSchema =
genericDeclareNamedSchema
defaultSchemaOptions {fieldLabelModifier = \fieldLabel -> drop 4 fieldLabel}
instance Arbitrary SearchInQuery where
arbitrary = SearchInQuery <$> arbitrary
-----------------------------------------------------------------------
data SearchResults = SearchResults { srs_results :: [FacetPaired Int UTCTime HyperdataDocument Int [Pair Int Text]]}
......@@ -75,3 +91,9 @@ type SearchAPI = Post '[JSON] SearchResults
search :: Connection -> SearchQuery -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> Handler SearchResults
search c (SearchQuery q pId) o l order =
liftIO $ SearchResults <$> searchInCorpusWithContacts c pId q o l order
searchIn :: Connection -> NodeId -> SearchInQuery -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> Handler SearchResults
searchIn c nId (SearchInQuery q ) o l order =
liftIO $ SearchResults <$> searchInCorpusWithContacts c nId q o l order
......@@ -151,7 +151,7 @@ subFlowCorpus username cName = do
True -> panic "Error: more than 1 userNode / user"
False -> pure rootId'
let rootId = maybe (panic "error rootId") identity (head rootId'')
--{-
corpusId'' <- if username == userMaster
then do
ns <- runCmd' $ getCorporaWithParentId' rootId
......@@ -159,7 +159,6 @@ subFlowCorpus username cName = do
else
pure []
--}
corpusId' <- if corpusId'' /= []
then pure corpusId''
else runCmd' $ mkCorpus (Just cName) Nothing rootId userId
......
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