Commit 143840d4 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[TABLE] search in docs, result as Facet.

parent cc89bb12
Pipeline #529 failed with stage
...@@ -51,7 +51,7 @@ import GHC.Generics (Generic) ...@@ -51,7 +51,7 @@ import GHC.Generics (Generic)
import Gargantext.API.Metrics import Gargantext.API.Metrics
import Gargantext.API.Ngrams (TabType(..), TableNgramsApi, apiNgramsTableCorpus, QueryParamR, TODO) import Gargantext.API.Ngrams (TabType(..), TableNgramsApi, apiNgramsTableCorpus, QueryParamR, TODO)
import Gargantext.API.Ngrams.NTree (MyTree) import Gargantext.API.Ngrams.NTree (MyTree)
import Gargantext.API.Search (SearchDocsAPI, searchDocs) import Gargantext.API.Search (SearchDocsAPI, searchDocs, SearchQuery(..))
import Gargantext.API.Types import Gargantext.API.Types
import Gargantext.Core.Types (Offset, Limit) import Gargantext.Core.Types (Offset, Limit)
import Gargantext.Core.Types.Main (Tree, NodeTree, ListType) import Gargantext.Core.Types.Main (Tree, NodeTree, ListType)
...@@ -62,6 +62,7 @@ import Gargantext.Database.Schema.Node ( getNodesWithParentId, getNode, getNode' ...@@ -62,6 +62,7 @@ import Gargantext.Database.Schema.Node ( getNodesWithParentId, getNode, getNode'
import Gargantext.Database.Schema.NodeNode (nodeNodesCategory) import Gargantext.Database.Schema.NodeNode (nodeNodesCategory)
import Gargantext.Database.Tree (treeDB) import Gargantext.Database.Tree (treeDB)
import Gargantext.Database.Types.Node import Gargantext.Database.Types.Node
import Gargantext.Database.TextSearch
import Gargantext.Database.Utils -- (Cmd, CmdM) import Gargantext.Database.Utils -- (Cmd, CmdM)
import Gargantext.Database.Learn (FavOrTrash(..), moreLike) import Gargantext.Database.Learn (FavOrTrash(..), moreLike)
import Gargantext.Prelude import Gargantext.Prelude
...@@ -163,28 +164,28 @@ type ChildrenApi a = Summary " Summary children" ...@@ -163,28 +164,28 @@ type ChildrenApi a = Summary " Summary children"
-- TODO: make the NodeId type indexed by `a`, then we no longer need the proxy. -- TODO: make the NodeId type indexed by `a`, then we no longer need the proxy.
nodeAPI :: JSONB a => proxy a -> UserId -> NodeId -> GargServer (NodeAPI a) nodeAPI :: JSONB a => proxy a -> UserId -> NodeId -> GargServer (NodeAPI a)
nodeAPI p uId id nodeAPI p uId id
= getNode id p = getNode id p
:<|> rename id :<|> rename id
:<|> postNode uId id :<|> postNode uId id
:<|> putNode id :<|> putNode id
:<|> deleteNodeApi id :<|> deleteNodeApi id
:<|> getChildren id p :<|> getChildren id p
-- TODO gather it -- TODO gather it
:<|> getTable id :<|> tableApi id
:<|> apiNgramsTableCorpus id :<|> apiNgramsTableCorpus id
:<|> getPairing id :<|> getPairing id
-- :<|> getTableNgramsDoc id -- :<|> getTableNgramsDoc id
:<|> catApi id :<|> catApi id
:<|> searchDocs id :<|> searchDocs id
:<|> getScatter id :<|> getScatter id
:<|> getChart id :<|> getChart id
:<|> getPie id :<|> getPie id
:<|> getTree id :<|> getTree id
:<|> phyloAPI id uId :<|> phyloAPI id uId
:<|> postUpload id :<|> postUpload id
where where
deleteNodeApi id' = do deleteNodeApi id' = do
...@@ -238,15 +239,17 @@ catApi = putCat ...@@ -238,15 +239,17 @@ catApi = putCat
------------------------------------------------------------------------ ------------------------------------------------------------------------
type TableApi = Summary " Table API" type TableApi = Summary " Table API"
:> ReqBody '[JSON] SearchQuery
:> QueryParam "view" TabType :> QueryParam "view" TabType
:> QueryParam "offset" Int :> QueryParam "offset" Int
:> QueryParam "limit" Int :> QueryParam "limit" Int
:> QueryParam "order" OrderBy :> QueryParam "order" OrderBy
:> Get '[JSON] [FacetDoc] :> Post '[JSON] [FacetDoc]
-- TODO adapt FacetDoc -> ListDoc (and add type of document as column) -- TODO adapt FacetDoc -> ListDoc (and add type of document as column)
type PairingApi = Summary " Pairing API" type PairingApi = Summary " Pairing API"
:> QueryParam "view" TabType -- TODO change TabType -> DocType (CorpusId for pairing) :> QueryParam "view" TabType
-- TODO change TabType -> DocType (CorpusId for pairing)
:> QueryParam "offset" Int :> QueryParam "offset" Int
:> QueryParam "limit" Int :> QueryParam "limit" Int
:> QueryParam "order" OrderBy :> QueryParam "order" OrderBy
...@@ -271,8 +274,6 @@ type TreeApi = Summary " Tree API" ...@@ -271,8 +274,6 @@ type TreeApi = Summary " Tree API"
:> QueryParamR "listType" ListType :> QueryParamR "listType" ListType
:> Get '[JSON] (ChartMetrics [MyTree]) :> Get '[JSON] (ChartMetrics [MyTree])
-- Depending on the Type of the Node, we could post -- Depending on the Type of the Node, we could post
-- New documents for a corpus -- New documents for a corpus
-- New map list terms -- New map list terms
...@@ -323,6 +324,16 @@ treeAPI = treeDB ...@@ -323,6 +324,16 @@ treeAPI = treeDB
rename :: NodeId -> RenameNode -> Cmd err [Int] rename :: NodeId -> RenameNode -> Cmd err [Int]
rename nId (RenameNode name') = U.update (U.Rename nId name') rename nId (RenameNode name') = U.update (U.Rename nId name')
tableApi :: NodeId -> SearchQuery
-> Maybe TabType
-> Maybe Offset -> Maybe Limit
-> Maybe OrderBy -> Cmd err [FacetDoc]
tableApi cId (SearchQuery []) ft o l order = getTable cId ft o l order
tableApi cId (SearchQuery q) ft o l order = case ft of
Just Docs -> searchInCorpus cId q o l order
Just Trash -> panic "TODO search in Trash" -- TODO searchInCorpus cId q o l order
_ -> panic "not implemented: search in Fav/Trash/*"
getTable :: NodeId -> Maybe TabType getTable :: NodeId -> Maybe TabType
-> Maybe Offset -> Maybe Limit -> Maybe Offset -> Maybe Limit
-> Maybe OrderBy -> Cmd err [FacetDoc] -> Maybe OrderBy -> Cmd err [FacetDoc]
......
...@@ -56,7 +56,6 @@ instance Arbitrary SearchQuery where ...@@ -56,7 +56,6 @@ instance Arbitrary SearchQuery where
arbitrary = elements [SearchQuery ["electrodes"]] arbitrary = elements [SearchQuery ["electrodes"]]
----------------------------------------------------------------------- -----------------------------------------------------------------------
data SearchDocResults = SearchDocResults { sdr_results :: [FacetDoc]} data SearchDocResults = SearchDocResults { sdr_results :: [FacetDoc]}
deriving (Generic) deriving (Generic)
$(deriveJSON (unPrefix "sdr_") ''SearchDocResults) $(deriveJSON (unPrefix "sdr_") ''SearchDocResults)
......
{-| {-|
Module : Gargantext.Database.Learn Module : Gargantext.Database.Learn
Description : Learn Small Data Analytics with big data connection (DB) Description : Learn Small Data Analytics with big data connection (DB)
Copyright : (c) CNRS, 2017-Present opyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
Maintainer : team@gargantext.org Maintainer : team@gargantext.org
Stability : experimental Stability : experimental
...@@ -44,11 +44,13 @@ moreLike cId o l order ft = do ...@@ -44,11 +44,13 @@ moreLike cId o l order ft = do
--------------------------------------------------------------------------- ---------------------------------------------------------------------------
getPriors :: FavOrTrash -> CorpusId -> Cmd err (Events Bool) getPriors :: FavOrTrash -> CorpusId -> Cmd err (Events Bool)
getPriors ft cId = do getPriors ft cId = do
docs_trash <- runViewDocuments cId True Nothing Nothing Nothing
docs_fav <- filter (\(FacetDoc _ _ _ _ f _) -> f == 2) docs_fav <- filter (\(FacetDoc _ _ _ _ f _) -> f == 2)
<$> runViewDocuments cId False Nothing Nothing Nothing <$> runViewDocuments cId False Nothing Nothing Nothing
docs_trash <- List.take (List.length docs_fav)
<$> runViewDocuments cId True Nothing Nothing Nothing
let priors = priorEventsWith text (fav2bool ft) ( List.zip (repeat False) docs_fav let priors = priorEventsWith text (fav2bool ft) ( List.zip (repeat False) docs_fav
<> List.zip (repeat True ) docs_trash <> List.zip (repeat True ) docs_trash
...@@ -59,15 +61,15 @@ getPriors ft cId = do ...@@ -59,15 +61,15 @@ getPriors ft cId = do
moreLikeWith :: CorpusId -> Maybe Offset -> Maybe Limit -> Maybe OrderBy moreLikeWith :: CorpusId -> Maybe Offset -> Maybe Limit -> Maybe OrderBy
-> FavOrTrash -> Events Bool -> Cmd err [FacetDoc] -> FavOrTrash -> Events Bool -> Cmd err [FacetDoc]
moreLikeWith cId o l order ft priors = do moreLikeWith cId o l order ft priors = do
docs_test <- filter (\(FacetDoc _ _ _ _ f _) -> f == 0) docs_test <- filter (\(FacetDoc _ _ _ _ f _) -> f == 1)
<$> runViewDocuments cId False o l order <$> runViewDocuments cId False o Nothing order
let results = map fst let results = map fst
$ filter ((==) (Just $ not $ fav2bool ft) . snd) $ filter ((==) (Just $ not $ fav2bool ft) . snd)
$ map (\f -> (f, detectDefaultWithPriors text priors f)) docs_test $ map (\f -> (f, detectDefaultWithPriors text priors f)) docs_test
pure results pure $ List.take (maybe 10 identity l) results
--------------------------------------------------------------------------- ---------------------------------------------------------------------------
fav2bool :: FavOrTrash -> Bool fav2bool :: FavOrTrash -> Bool
......
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