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

[WIP] Starting query Garg for a Hello Word.

parent 5897de6c
...@@ -406,8 +406,8 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid)) ...@@ -406,8 +406,8 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
-- TODO access -- TODO access
-- :<|> addUpload -- :<|> addUpload
-- :<|> (\corpus -> addWithQuery corpus :<|> addWithFile corpus) -- :<|> (\corpus -> addWithQuery corpus :<|> addWithFile corpus)
:<|> addCorpusWithForm (UserDBId uid) -- "user1" :<|> addCorpusWithForm (UserDBId uid)
:<|> addCorpusWithQuery :<|> addCorpusWithQuery (RootId uid)
:<|> addAnnuaireWithForm :<|> addAnnuaireWithForm
-- :<|> New.api uid -- TODO-SECURITY -- :<|> New.api uid -- TODO-SECURITY
...@@ -416,16 +416,10 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid)) ...@@ -416,16 +416,10 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
:<|> waitAPI :<|> waitAPI
{- addCorpusWithQuery :: User -> GargServer New.AddWithQuery
addUpload :: GargServer New.Upload addCorpusWithQuery user cid =
addUpload cId = (serveJobsAPI $ JobFunction (\i log -> New.addToCorpusJobFunction cid i (liftBase . log)))
:<|> (serveJobsAPI $ JobFunction (\i log -> New.addToCorpusWithForm cid i (liftBase . log)))
--}
addCorpusWithQuery :: GargServer New.AddWithQuery
addCorpusWithQuery cid =
serveJobsAPI $ serveJobsAPI $
JobFunction (\i log -> New.addToCorpusJobFunction cid i (liftBase . log)) JobFunction (\i log -> New.addToCorpusWithQuery user cid i (liftBase . log))
addWithFile :: GargServer New.AddWithFile addWithFile :: GargServer New.AddWithFile
addWithFile cid i f = addWithFile cid i f =
......
...@@ -82,7 +82,7 @@ type Api = PostApi ...@@ -82,7 +82,7 @@ type Api = PostApi
type PostApi = Summary "New Corpus endpoint" type PostApi = Summary "New Corpus endpoint"
:> ReqBody '[JSON] Query :> ReqBody '[JSON] Query
:> Post '[JSON] CorpusId :> Post '[JSON] CorpusId
type GetApi = Get '[JSON] ApiInfo type GetApi = Get '[JSON] ApiInfo
-- | TODO manage several apis -- | TODO manage several apis
...@@ -182,18 +182,26 @@ type AddWithForm = Summary "Add with FormUrlEncoded to corpus endpoint" ...@@ -182,18 +182,26 @@ type AddWithForm = Summary "Add with FormUrlEncoded to corpus endpoint"
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- TODO WithQuery also has a corpus id -- TODO WithQuery also has a corpus id
addToCorpusJobFunction :: FlowCmdM env err m addToCorpusWithQuery :: FlowCmdM env err m
=> CorpusId => User
-> CorpusId
-> WithQuery -> WithQuery
-> (ScraperStatus -> m ()) -> (ScraperStatus -> m ())
-> m ScraperStatus -> m ScraperStatus
addToCorpusJobFunction _cid (WithQuery _q _dbs _l) logStatus = do addToCorpusWithQuery u cid (WithQuery q _dbs l) logStatus = do
-- TODO ... -- TODO ...
logStatus ScraperStatus { _scst_succeeded = Just 10 logStatus ScraperStatus { _scst_succeeded = Just 10
, _scst_failed = Just 2 , _scst_failed = Just 2
, _scst_remaining = Just 138 , _scst_remaining = Just 138
, _scst_events = Just [] , _scst_events = Just []
} }
printDebug "addToCorpusWithQuery" cid
-- TODO add cid
-- TODO if cid is folder -> create Corpus
-- if cid is corpus -> add to corpus
-- if cid is root -> create corpus in Private
cids <- flowCorpusSearchInDatabase u (maybe EN identity l) q
printDebug "corpus id" cids
-- TODO ... -- TODO ...
pure ScraperStatus { _scst_succeeded = Just 137 pure ScraperStatus { _scst_succeeded = Just 137
, _scst_failed = Just 13 , _scst_failed = Just 13
......
...@@ -20,10 +20,11 @@ module Gargantext.Core.Types.Individu ...@@ -20,10 +20,11 @@ module Gargantext.Core.Types.Individu
import Gargantext.Prelude hiding (reverse) import Gargantext.Prelude hiding (reverse)
import Data.Text (Text, pack, reverse) import Data.Text (Text, pack, reverse)
import Gargantext.Database.Types.Node (NodeId)
type UserId = Int type UserId = Int
data User = UserDBId UserId | UserName Text data User = UserDBId UserId | UserName Text | RootId NodeId
deriving (Eq) deriving (Eq)
type Username = Text type Username = Text
......
...@@ -213,9 +213,9 @@ flowCorpusUser :: (FlowCmdM env err m, MkCorpus c) ...@@ -213,9 +213,9 @@ flowCorpusUser :: (FlowCmdM env err m, MkCorpus c)
-> Maybe c -> Maybe c
-> [NodeId] -> [NodeId]
-> m CorpusId -> m CorpusId
flowCorpusUser l userName corpusName ctype ids = do flowCorpusUser l user corpusName ctype ids = do
-- User Flow -- User Flow
(userId, _rootId, userCorpusId) <- getOrMk_RootWithCorpus userName corpusName ctype (userId, _rootId, userCorpusId) <- getOrMk_RootWithCorpus user corpusName ctype
listId <- getOrMkList userCorpusId userId listId <- getOrMkList userCorpusId userId
_cooc <- mkNode NodeListCooc listId userId _cooc <- mkNode NodeListCooc listId userId
-- TODO: check if present already, ignore -- TODO: check if present already, ignore
...@@ -337,9 +337,9 @@ getOrMk_RootWithCorpus :: (HasNodeError err, MkCorpus a) ...@@ -337,9 +337,9 @@ getOrMk_RootWithCorpus :: (HasNodeError err, MkCorpus a)
-> Either CorpusName [CorpusId] -> Either CorpusName [CorpusId]
-> Maybe a -> Maybe a
-> Cmd err (UserId, RootId, CorpusId) -> Cmd err (UserId, RootId, CorpusId)
getOrMk_RootWithCorpus username cName c = do getOrMk_RootWithCorpus user cName c = do
(userId, rootId) <- getOrMkRoot username (userId, rootId) <- getOrMkRoot user
corpusId'' <- if username == UserName userMaster corpusId'' <- if user == UserName userMaster
then do then do
ns <- getCorporaWithParentId rootId ns <- getCorporaWithParentId rootId
pure $ map _node_id ns pure $ map _node_id ns
......
...@@ -179,6 +179,9 @@ getUserId :: HasNodeError err ...@@ -179,6 +179,9 @@ getUserId :: HasNodeError err
=> User => User
-> Cmd err UserId -> Cmd err UserId
getUserId (UserDBId uid) = pure uid getUserId (UserDBId uid) = pure uid
getUserId (RootId rid) = do
n <- getNode rid
pure $ _node_userId n
getUserId (UserName u ) = do getUserId (UserName u ) = do
muser <- getUser u muser <- getUser u
case muser of case muser of
......
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