Commit 82135cd7 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] ApiNgramsTableDoc specs todo.

parent 37e49cce
...@@ -66,23 +66,23 @@ import Servant.Swagger.UI ...@@ -66,23 +66,23 @@ import Servant.Swagger.UI
import Text.Blaze.Html (Html) import Text.Blaze.Html (Html)
--import Gargantext.API.Swagger --import Gargantext.API.Swagger
import Gargantext.Prelude
import Gargantext.Core.Types (HasInvalidError(..))
import Gargantext.API.FrontEnd (FrontEndAPI, frontEndServer)
--import Gargantext.Database.Node.Contact (HyperdataContact)
import Gargantext.API.Auth (AuthRequest, AuthResponse, auth) import Gargantext.API.Auth (AuthRequest, AuthResponse, auth)
import Gargantext.API.Ngrams (HasRepo(..), HasRepoSaver(..), saveRepo) import Gargantext.API.Count ( CountAPI, count, Query)
import Gargantext.API.Types import Gargantext.API.FrontEnd (FrontEndAPI, frontEndServer)
import Gargantext.API.Ngrams (HasRepo(..), HasRepoSaver(..), saveRepo, ApiNgramsTableDoc, apiNgramsTableDoc)
import Gargantext.API.Node import Gargantext.API.Node
import Gargantext.API.Search ( SearchAPI, search, SearchQuery)
import Gargantext.API.Types
import Gargantext.Core.Types (HasInvalidError(..))
import Gargantext.Database.Facet
import Gargantext.Database.Schema.Node (HasNodeError(..), NodeError) import Gargantext.Database.Schema.Node (HasNodeError(..), NodeError)
--import Gargantext.Database.Node.Contact (HyperdataContact)
import Gargantext.Database.Types.Node
import Gargantext.Database.Utils (HasConnection)
import Gargantext.Database.Tree (HasTreeError(..), TreeError) import Gargantext.Database.Tree (HasTreeError(..), TreeError)
import Gargantext.Database.Types.Node
import Gargantext.Database.Types.Node (NodeId, CorpusId, AnnuaireId) import Gargantext.Database.Types.Node (NodeId, CorpusId, AnnuaireId)
import Gargantext.API.Count ( CountAPI, count, Query) import Gargantext.Database.Utils (HasConnection)
import Gargantext.API.Search ( SearchAPI, search, SearchQuery) import Gargantext.Prelude
import Gargantext.Database.Facet
import Gargantext.Viz.Graph.API import Gargantext.Viz.Graph.API
--import Gargantext.API.Orchestrator --import Gargantext.API.Orchestrator
...@@ -248,6 +248,10 @@ type GargAPI' = ...@@ -248,6 +248,10 @@ type GargAPI' =
:<|> "annuaire":> Summary "Annuaire endpoint" :<|> "annuaire":> Summary "Annuaire endpoint"
:> Capture "id" AnnuaireId :> NodeAPI HyperdataAnnuaire :> Capture "id" AnnuaireId :> NodeAPI HyperdataAnnuaire
-- Document endpoint
:<|> "document":> Summary "Document endpoint"
:> Capture "id" DocId :> "ngrams" :> ApiNgramsTableDoc
-- Corpus endpoint -- Corpus endpoint
:<|> "nodes" :> Summary "Nodes endpoint" :<|> "nodes" :> Summary "Nodes endpoint"
:> ReqBody '[JSON] [NodeId] :> NodesAPI :> ReqBody '[JSON] [NodeId] :> NodesAPI
...@@ -310,6 +314,7 @@ serverGargAPI -- orchestrator ...@@ -310,6 +314,7 @@ serverGargAPI -- orchestrator
:<|> nodeAPI (Proxy :: Proxy HyperdataAny) fakeUserId :<|> nodeAPI (Proxy :: Proxy HyperdataAny) fakeUserId
:<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) fakeUserId :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) fakeUserId
:<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) fakeUserId :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) fakeUserId
:<|> apiNgramsTableDoc
:<|> nodesAPI :<|> nodesAPI
:<|> count -- TODO: undefined :<|> count -- TODO: undefined
:<|> search :<|> search
......
...@@ -612,29 +612,6 @@ ngramsIdPatch = fromList $ catMaybes $ reverse [ replace (1::NgramsId) (Just $ n ...@@ -612,29 +612,6 @@ ngramsIdPatch = fromList $ catMaybes $ reverse [ replace (1::NgramsId) (Just $ n
------------------------------------------------------------------------ ------------------------------------------------------------------------
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- TODO: find a better place for this Gargantext.API.{Common|Prelude|Core} ?
type QueryParamR = QueryParam' '[Required, Strict]
type TableNgramsApiGet = Summary " Table Ngrams API Get"
:> QueryParamR "ngramsType" TabType
:> QueryParamR "list" ListId
:> QueryParamR "limit" Limit
:> QueryParam "offset" Offset
:> QueryParam "listType" ListType
:> QueryParam "minTermSize" Int
:> QueryParam "maxTermSize" Int
:> QueryParam "search" Text
:> Get '[JSON] (Versioned NgramsTable)
type TableNgramsApi = Summary " Table Ngrams API Change"
:> QueryParamR "ngramsType" TabType
:> QueryParamR "list" ListId
:> ReqBody '[JSON] (Versioned NgramsTablePatch)
:> Put '[JSON] (Versioned NgramsTablePatch)
{- {-
-- TODO: Replace.old is ignored which means that if the current list -- TODO: Replace.old is ignored which means that if the current list
-- `GraphTerm` and that the patch is `Replace CandidateTerm StopTerm` then -- `GraphTerm` and that the patch is `Replace CandidateTerm StopTerm` then
...@@ -810,11 +787,11 @@ putListNgrams listId ngramsType nes = do ...@@ -810,11 +787,11 @@ putListNgrams listId ngramsType nes = do
-- Apply the given patch to the DB and returns the patch to be applied on the -- Apply the given patch to the DB and returns the patch to be applied on the
-- client. -- client.
tableNgramsPatch :: (HasInvalidError err, RepoCmdM env err m) tableNgramsPut :: (HasInvalidError err, RepoCmdM env err m)
=> CorpusId -> TabType -> ListId => CorpusId -> TabType -> ListId
-> Versioned NgramsTablePatch -> Versioned NgramsTablePatch
-> m (Versioned NgramsTablePatch) -> m (Versioned NgramsTablePatch)
tableNgramsPatch _corpusId tabType listId (Versioned p_version p_table) tableNgramsPut _corpusId tabType listId (Versioned p_version p_table)
| p_table == mempty = do | p_table == mempty = do
let ngramsType = ngramsTypeFromTabType tabType let ngramsType = ngramsTypeFromTabType tabType
...@@ -889,34 +866,6 @@ type MaxSize = Int ...@@ -889,34 +866,6 @@ type MaxSize = Int
getTableNgramsCorpus :: (RepoCmdM env err m, HasNodeError err, HasConnection env)
=> NodeId -> TabType
-> ListId -> Limit -> Maybe Offset
-> Maybe ListType
-> Maybe MinSize -> Maybe MaxSize
-> Maybe Text -- full text search
-> m (Versioned NgramsTable)
getTableNgramsCorpus nId tabType listId limit_ offset listType minSize maxSize mt =
getTableNgrams nId tabType listId limit_ offset listType minSize maxSize searchQuery
where
searchQuery = maybe (const True) isInfixOf mt
-- | Text search is deactivated for now for ngrams by doc only
getTableNgramsDoc :: (RepoCmdM env err m, HasNodeError err, HasConnection env)
=> CorpusId -> DocId -> TabType
-> ListId -> Limit -> Maybe Offset
-> Maybe ListType
-> Maybe MinSize -> Maybe MaxSize
-> Maybe Text -- full text search
-> m (Versioned NgramsTable)
getTableNgramsDoc cId dId tabType listId limit_ offset listType minSize maxSize _mt = do
ns <- selectNodesWithUsername NodeList userMaster
let ngramsType = ngramsTypeFromTabType tabType
ngs <- selectNgramsByDoc (ns <> [cId]) dId ngramsType
let searchQuery = flip S.member (S.fromList ngs)
getTableNgrams cId tabType listId limit_ offset listType minSize maxSize searchQuery
getTableNgrams :: (RepoCmdM env err m, HasNodeError err, HasConnection env) getTableNgrams :: (RepoCmdM env err m, HasNodeError err, HasConnection env)
=> NodeId -> TabType => NodeId -> TabType
-> ListId -> Limit -> Maybe Offset -> ListId -> Limit -> Maybe Offset
...@@ -968,3 +917,78 @@ getTableNgrams nId tabType listId limit_ offset ...@@ -968,3 +917,78 @@ getTableNgrams nId tabType listId limit_ offset
pure $ table & v_data . _NgramsTable . each %~ setOcc pure $ table & v_data . _NgramsTable . each %~ setOcc
-- APIs
-- TODO: find a better place for the code above, All APIs stay here
type QueryParamR = QueryParam' '[Required, Strict]
type TableNgramsApiGet = Summary " Table Ngrams API Get"
:> QueryParamR "ngramsType" TabType
:> QueryParamR "list" ListId
:> QueryParamR "limit" Limit
:> QueryParam "offset" Offset
:> QueryParam "listType" ListType
:> QueryParam "minTermSize" Int
:> QueryParam "maxTermSize" Int
:> QueryParam "search" Text
:> Get '[JSON] (Versioned NgramsTable)
type TableNgramsApiPut = Summary " Table Ngrams API Change"
:> QueryParamR "ngramsType" TabType
:> QueryParamR "list" ListId
:> ReqBody '[JSON] (Versioned NgramsTablePatch)
:> Put '[JSON] (Versioned NgramsTablePatch)
getTableNgramsCorpus :: (RepoCmdM env err m, HasNodeError err, HasConnection env)
=> NodeId -> TabType
-> ListId -> Limit -> Maybe Offset
-> Maybe ListType
-> Maybe MinSize -> Maybe MaxSize
-> Maybe Text -- full text search
-> m (Versioned NgramsTable)
getTableNgramsCorpus nId tabType listId limit_ offset listType minSize maxSize mt =
getTableNgrams nId tabType listId limit_ offset listType minSize maxSize searchQuery
where
searchQuery = maybe (const True) isInfixOf mt
-- | Text search is deactivated for now for ngrams by doc only
getTableNgramsDoc :: (RepoCmdM env err m, HasNodeError err, HasConnection env)
=> DocId -> TabType
-> ListId -> Limit -> Maybe Offset
-> Maybe ListType
-> Maybe MinSize -> Maybe MaxSize
-> Maybe Text -- full text search
-> m (Versioned NgramsTable)
getTableNgramsDoc dId tabType listId limit_ offset listType minSize maxSize _mt = do
ns <- selectNodesWithUsername NodeList userMaster
let ngramsType = ngramsTypeFromTabType tabType
ngs <- selectNgramsByDoc (ns <> [listId]) dId ngramsType
let searchQuery = flip S.member (S.fromList ngs)
getTableNgrams dId tabType listId limit_ offset listType minSize maxSize searchQuery
--{-
-- TODO Doc Table Ngrams API
type ApiNgramsTableDoc = TableNgramsApiGet
-- :<|> TableNgramsApiPut
-- :<|> TableNgramsApiPost
apiNgramsTableDoc :: (RepoCmdM env err m, HasNodeError err, HasConnection env)
=> DocId -> TabType
-> ListId -> Limit -> Maybe Offset
-> Maybe ListType
-> Maybe MinSize -> Maybe MaxSize
-> Maybe Text -- full text search
-> m (Versioned NgramsTable)
{- TODO
--apiDocNgramsTable :: ApiDocNgramsTable
--apiDocNgramsTable :: ApiDocNgramsTable
--apiDocNgramsTable = getTableNgramsDoc
:<|> tableNgramsPut
:<|> tableNgramsPost
--}
apiNgramsTableDoc = getTableNgramsDoc
...@@ -45,7 +45,7 @@ import Data.Text (Text()) ...@@ -45,7 +45,7 @@ import Data.Text (Text())
import Data.Time (UTCTime) import Data.Time (UTCTime)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Metrics import Gargantext.API.Metrics
import Gargantext.API.Ngrams (TabType(..), TableNgramsApi, TableNgramsApiGet, tableNgramsPatch, getTableNgramsCorpus, QueryParamR) import Gargantext.API.Ngrams (TabType(..), TableNgramsApiPut, TableNgramsApiGet, tableNgramsPut, getTableNgramsCorpus, QueryParamR)
import Gargantext.API.Search ( SearchAPI, searchIn, SearchInQuery) import Gargantext.API.Search ( SearchAPI, searchIn, SearchInQuery)
import Gargantext.API.Types import Gargantext.API.Types
import Gargantext.Core.Types (Offset, Limit) import Gargantext.Core.Types (Offset, Limit)
...@@ -122,10 +122,9 @@ type NodeAPI a = Get '[JSON] (Node a) ...@@ -122,10 +122,9 @@ type NodeAPI a = Get '[JSON] (Node a)
-- TODO gather it -- TODO gather it
:<|> "table" :> TableApi :<|> "table" :> TableApi
:<|> "list" :> TableNgramsApi
:<|> "listGet" :> TableNgramsApiGet :<|> "listGet" :> TableNgramsApiGet
:<|> "list" :> TableNgramsApiPut
:<|> "pairing" :> PairingApi :<|> "pairing" :> PairingApi
-- :<|> "document" :> Capture "docId" :> "list" :> TableNgramsApiGet
:<|> "favorites" :> FavApi :<|> "favorites" :> FavApi
:<|> "documents" :> DocsApi :<|> "documents" :> DocsApi
...@@ -171,8 +170,8 @@ nodeAPI p uId id ...@@ -171,8 +170,8 @@ nodeAPI p uId id
-- TODO gather it -- TODO gather it
:<|> getTable id :<|> getTable id
:<|> tableNgramsPatch id
:<|> getTableNgramsCorpus id :<|> getTableNgramsCorpus id
:<|> tableNgramsPut id
:<|> getPairing id :<|> getPairing id
-- :<|> getTableNgramsDoc id -- :<|> getTableNgramsDoc id
......
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