Commit 6507a2d2 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] reindexing enabled in frontend

parent d97e2510
...@@ -115,7 +115,7 @@ import Gargantext.Database.Query.Table.Ngrams hiding (NgramsType(..), ngramsType ...@@ -115,7 +115,7 @@ import Gargantext.Database.Query.Table.Ngrams hiding (NgramsType(..), ngramsType
import Gargantext.Database.Query.Table.Node (getNode) import Gargantext.Database.Query.Table.Node (getNode)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError) import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Query.Table.Node.Select import Gargantext.Database.Query.Table.Node.Select
import Gargantext.Database.Schema.Node (node_id, node_parentId, node_userId) import Gargantext.Database.Schema.Node (node_id, node_parent_id, node_user_id)
import Gargantext.Prelude hiding (log) import Gargantext.Prelude hiding (log)
import Gargantext.Prelude.Job import Gargantext.Prelude.Job
import Gargantext.Prelude.Clock (hasTime, getTime) import Gargantext.Prelude.Clock (hasTime, getTime)
...@@ -368,8 +368,8 @@ tableNgramsPostChartsAsync utn logStatus = do ...@@ -368,8 +368,8 @@ tableNgramsPostChartsAsync utn logStatus = do
node <- getNode listId node <- getNode listId
let nId = node ^. node_id let nId = node ^. node_id
_uId = node ^. node_userId _uId = node ^. node_user_id
mCId = node ^. node_parentId mCId = node ^. node_parent_id
printDebug "[tableNgramsPut] tabType" tabType printDebug "[tableNgramsPut] tabType" tabType
printDebug "[tableNgramsPut] listId" listId printDebug "[tableNgramsPut] listId" listId
......
...@@ -61,7 +61,7 @@ postNode :: HasNodeError err ...@@ -61,7 +61,7 @@ postNode :: HasNodeError err
-> Cmd err [NodeId] -> Cmd err [NodeId]
postNode uId pId (PostNode nodeName nt) = do postNode uId pId (PostNode nodeName nt) = do
nodeUser <- getNodeUser (NodeId uId) nodeUser <- getNodeUser (NodeId uId)
let uId' = nodeUser ^. node_userId let uId' = nodeUser ^. node_user_id
mkNodeWithParent nt (Just pId) uId' nodeName mkNodeWithParent nt (Just pId) uId' nodeName
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -100,7 +100,7 @@ postNodeAsync uId nId (PostNode nodeName tn) logStatus = do ...@@ -100,7 +100,7 @@ postNodeAsync uId nId (PostNode nodeName tn) logStatus = do
, _scst_events = Just [] , _scst_events = Just []
} }
let uId' = nodeUser ^. node_userId let uId' = nodeUser ^. node_user_id
_ <- mkNodeWithParent tn (Just nId) uId' nodeName _ <- mkNodeWithParent tn (Just nId) uId' nodeName
pure JobLog { _scst_succeeded = Just 3 pure JobLog { _scst_succeeded = Just 3
......
...@@ -16,25 +16,31 @@ Portability : POSIX ...@@ -16,25 +16,31 @@ Portability : POSIX
module Gargantext.API.Node.Update module Gargantext.API.Node.Update
where where
import Control.Lens (view)
import Data.Aeson import Data.Aeson
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Swagger import Data.Swagger
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Prelude (Enum, Bounded, minBound, maxBound)
import Servant
import Servant.Job.Async (JobFunction(..), serveJobsAPI)
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs) import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
import Gargantext.API.Admin.Types (HasSettings) import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.Ngrams.List (reIndexWith)
import Gargantext.API.Prelude (GargServer, simuLogs) import Gargantext.API.Prelude (GargServer, simuLogs)
import Gargantext.Core.Viz.Graph.API (recomputeGraph)
import Gargantext.Core.Methods.Distances (GraphMetric(..)) import Gargantext.Core.Methods.Distances (GraphMetric(..))
import Gargantext.Core.Viz.Graph.API (recomputeGraph)
import Gargantext.Database.Query.Table.Node (getNode)
import Gargantext.Database.Schema.Node (node_parent_id)
import Gargantext.Core.Types.Main (ListType(..))
import Gargantext.Database.Schema.Ngrams (NgramsType(NgramsTerms))
import Gargantext.Database.Action.Flow.Pairing (pairing) import Gargantext.Database.Action.Flow.Pairing (pairing)
import Gargantext.Database.Action.Flow.Types (FlowCmdM) import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Prelude (Ord, Eq, (<$>), ($), liftBase, (.), printDebug, pure, show, cs, (<>), panic) import Gargantext.Prelude (Ord, Eq, (<$>), ($), liftBase, (.), printDebug, pure, show, cs, (<>), panic)
import Prelude (Enum, Bounded, minBound, maxBound)
import Servant
import Servant.Job.Async (JobFunction(..), serveJobsAPI)
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
import qualified Data.Set as Set
------------------------------------------------------------------------ ------------------------------------------------------------------------
type API = Summary " Update node according to NodeType params" type API = Summary " Update node according to NodeType params"
...@@ -112,6 +118,30 @@ updateNode _uId nid1 (LinkNodeReq nt nid2) logStatus = do ...@@ -112,6 +118,30 @@ updateNode _uId nid1 (LinkNodeReq nt nid2) logStatus = do
, _scst_events = Just [] , _scst_events = Just []
} }
updateNode _uId nId (UpdateNodeParamsList _mode) logStatus = do
logStatus JobLog { _scst_succeeded = Just 1
, _scst_failed = Just 0
, _scst_remaining = Just 2
, _scst_events = Just []
}
corpusId <- view node_parent_id <$> getNode nId
logStatus JobLog { _scst_succeeded = Just 2
, _scst_failed = Just 0
, _scst_remaining = Just 1
, _scst_events = Just []
}
_ <- case corpusId of
Just cId -> reIndexWith cId nId NgramsTerms (Set.singleton MapTerm)
Nothing -> pure ()
pure JobLog { _scst_succeeded = Just 3
, _scst_failed = Just 0
, _scst_remaining = Just 0
, _scst_events = Just []
}
updateNode _uId _nId _p logStatus = do updateNode _uId _nId _p logStatus = do
simuLogs logStatus 10 simuLogs logStatus 10
......
...@@ -43,7 +43,7 @@ import Gargantext.Database.Query.Table.Node.Select ...@@ -43,7 +43,7 @@ import Gargantext.Database.Query.Table.Node.Select
import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata) import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Database.Query.Table.Node.User (getNodeUser) import Gargantext.Database.Query.Table.Node.User (getNodeUser)
import Gargantext.Database.Schema.Ngrams import Gargantext.Database.Schema.Ngrams
import Gargantext.Database.Schema.Node (node_parentId, node_hyperdata, node_name, node_userId) import Gargantext.Database.Schema.Node (node_parent_id, node_hyperdata, node_name, node_user_id)
import Gargantext.Prelude import Gargantext.Prelude
import Servant import Servant
import Servant.Job.Async import Servant.Job.Async
...@@ -87,7 +87,7 @@ getGraph _uId nId = do ...@@ -87,7 +87,7 @@ getGraph _uId nId = do
camera = nodeGraph ^. node_hyperdata . hyperdataCamera camera = nodeGraph ^. node_hyperdata . hyperdataCamera
cId = maybe (panic "[G.V.G.API] Node has no parent") cId = maybe (panic "[G.V.G.API] Node has no parent")
identity identity
$ nodeGraph ^. node_parentId $ nodeGraph ^. node_parent_id
-- TODO Distance in Graph params -- TODO Distance in Graph params
case graph of case graph of
...@@ -123,7 +123,7 @@ recomputeGraph _uId nId maybeDistance = do ...@@ -123,7 +123,7 @@ recomputeGraph _uId nId maybeDistance = do
v = repo ^. r_version v = repo ^. r_version
cId = maybe (panic "[G.V.G.API.recomputeGraph] Node has no parent") cId = maybe (panic "[G.V.G.API.recomputeGraph] Node has no parent")
identity identity
$ nodeGraph ^. node_parentId $ nodeGraph ^. node_parent_id
similarity = case graphMetric of similarity = case graphMetric of
Nothing -> withMetric Order2 Nothing -> withMetric Order2
Just m -> withMetric m Just m -> withMetric m
...@@ -269,7 +269,7 @@ graphClone uId pId (HyperdataGraphAPI { _hyperdataAPIGraph = graph ...@@ -269,7 +269,7 @@ graphClone uId pId (HyperdataGraphAPI { _hyperdataAPIGraph = graph
let nodeType = NodeGraph let nodeType = NodeGraph
nodeUser <- getNodeUser (NodeId uId) nodeUser <- getNodeUser (NodeId uId)
nodeParent <- getNodeWith pId (Proxy :: Proxy HyperdataGraph) nodeParent <- getNodeWith pId (Proxy :: Proxy HyperdataGraph)
let uId' = nodeUser ^. node_userId let uId' = nodeUser ^. node_user_id
nIds <- mkNodeWithParent nodeType (Just pId) uId' $ nodeParent ^. node_name nIds <- mkNodeWithParent nodeType (Just pId) uId' $ nodeParent ^. node_name
case nIds of case nIds of
[] -> pure pId [] -> pure pId
......
...@@ -65,14 +65,6 @@ flowPhylo cId = do ...@@ -65,14 +65,6 @@ flowPhylo cId = do
-- | To filter the Ngrams of a document based on the termList -- | To filter the Ngrams of a document based on the termList
filterTerms :: Patterns -> (Date, Text) -> (Date, [Text]) filterTerms :: Patterns -> (Date, Text) -> (Date, [Text])
filterTerms patterns' (y,d) = (y,termsInText patterns' d) filterTerms patterns' (y,d) = (y,termsInText patterns' d)
where
--------------------------------------
termsInText :: Patterns -> Text -> [Text]
termsInText pats txt = List.nub
$ List.concat
$ map (map Text.unwords)
$ extractTermsWithList pats txt
--------------------------------------
docs = map ((\(y,t) -> Document y t) . filterTerms patterns) docs' docs = map ((\(y,t) -> Document y t) . filterTerms patterns) docs'
......
...@@ -47,7 +47,7 @@ deleteNode u nodeId = do ...@@ -47,7 +47,7 @@ deleteNode u nodeId = do
nt | nt == toDBid NodeUser -> panic "Not allowed to delete NodeUser (yet)" nt | nt == toDBid NodeUser -> panic "Not allowed to delete NodeUser (yet)"
nt | nt == toDBid NodeTeam -> do nt | nt == toDBid NodeTeam -> do
uId <- getUserId u uId <- getUserId u
if _node_userId node' == uId if _node_user_id node' == uId
then N.deleteNode nodeId then N.deleteNode nodeId
else delFolderTeam u nodeId else delFolderTeam u nodeId
nt | nt == toDBid NodeFile -> do nt | nt == toDBid NodeFile -> do
...@@ -62,7 +62,7 @@ deleteNode u nodeId = do ...@@ -62,7 +62,7 @@ deleteNode u nodeId = do
-- else if hasNodeType node' NodeTeam -- else if hasNodeType node' NodeTeam
-- then do -- then do
-- uId <- getUserId u -- uId <- getUserId u
-- if _node_userId node' == uId -- if _node_user_id node' == uId
-- then N.deleteNode nodeId -- then N.deleteNode nodeId
-- else delFolderTeam u nodeId -- else delFolderTeam u nodeId
-- else N.deleteNode nodeId -- else N.deleteNode nodeId
...@@ -49,7 +49,7 @@ shareNodeWith (ShareNodeWith_User NodeFolderShared u) n = do ...@@ -49,7 +49,7 @@ shareNodeWith (ShareNodeWith_User NodeFolderShared u) n = do
if not (hasNodeType nodeToCheck NodeTeam) if not (hasNodeType nodeToCheck NodeTeam)
then errorWith "[G.D.A.S.shareNodeWith] Can share node Team only" then errorWith "[G.D.A.S.shareNodeWith] Can share node Team only"
else else
if (view node_userId nodeToCheck == userIdCheck) if (view node_user_id nodeToCheck == userIdCheck)
then errorWith "[G.D.A.S.shareNodeWith] Can share to others only" then errorWith "[G.D.A.S.shareNodeWith] Can share to others only"
else do else do
folderSharedId <- getFolderId u NodeFolderShared folderSharedId <- getFolderId u NodeFolderShared
......
...@@ -53,7 +53,7 @@ getUserId' :: HasNodeError err ...@@ -53,7 +53,7 @@ getUserId' :: HasNodeError err
getUserId' (UserDBId uid) = pure (Just uid) getUserId' (UserDBId uid) = pure (Just uid)
getUserId' (RootId rid) = do getUserId' (RootId rid) = do
n <- getNode rid n <- getNode rid
pure $ Just $ _node_userId n pure $ Just $ _node_user_id n
getUserId' (UserName u ) = do getUserId' (UserName u ) = do
muser <- getUser u muser <- getUser u
case muser of case muser of
...@@ -77,7 +77,7 @@ getUsername (UserDBId i) = do ...@@ -77,7 +77,7 @@ getUsername (UserDBId i) = do
Nothing -> nodeError $ NodeError "G.D.A.U.getUserName: User not found with that id" Nothing -> nodeError $ NodeError "G.D.A.U.getUserName: User not found with that id"
getUsername (RootId rid) = do getUsername (RootId rid) = do
n <- getNode rid n <- getNode rid
getUsername (UserDBId $ _node_userId n) getUsername (UserDBId $ _node_user_id n)
getUsername UserPublic = pure "UserPublic" getUsername UserPublic = pure "UserPublic"
-------------------------------------------------------------------------- --------------------------------------------------------------------------
......
...@@ -264,10 +264,10 @@ insertNodesR ns = mkCmd $ \conn -> ...@@ -264,10 +264,10 @@ insertNodesR ns = mkCmd $ \conn ->
runInsert_ conn (Insert nodeTable ns (rReturning (\(Node i _ _ _ _ _ _ _) -> i)) Nothing) runInsert_ conn (Insert nodeTable ns (rReturning (\(Node i _ _ _ _ _ _ _) -> i)) Nothing)
insertNodesWithParent :: Maybe ParentId -> [NodeWrite] -> Cmd err Int64 insertNodesWithParent :: Maybe ParentId -> [NodeWrite] -> Cmd err Int64
insertNodesWithParent pid ns = insertNodes (set node_parentId (pgNodeId <$> pid) <$> ns) insertNodesWithParent pid ns = insertNodes (set node_parent_id (pgNodeId <$> pid) <$> ns)
insertNodesWithParentR :: Maybe ParentId -> [NodeWrite] -> Cmd err [NodeId] insertNodesWithParentR :: Maybe ParentId -> [NodeWrite] -> Cmd err [NodeId]
insertNodesWithParentR pid ns = insertNodesR (set node_parentId (pgNodeId <$> pid) <$> ns) insertNodesWithParentR pid ns = insertNodesR (set node_parent_id (pgNodeId <$> pid) <$> ns)
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- TODO -- TODO
-- currently this function removes the child relation -- currently this function removes the child relation
......
...@@ -38,5 +38,5 @@ selectNodesWithUsername nt u = runOpaQuery (q u) ...@@ -38,5 +38,5 @@ selectNodesWithUsername nt u = runOpaQuery (q u)
join' :: Query (NodeRead, UserReadNull) join' :: Query (NodeRead, UserReadNull)
join' = leftJoin queryNodeTable queryUserTable on1 join' = leftJoin queryNodeTable queryUserTable on1
where where
on1 (n,us) = _node_userId n .== user_id us on1 (n,us) = _node_user_id n .== user_id us
...@@ -182,7 +182,7 @@ findSharedDirect r nt nts fun = do ...@@ -182,7 +182,7 @@ findSharedDirect r nt nts fun = do
-- , " " -- , " "
-- , s ] -- , s ]
parent <- getNodeWith r (Proxy :: Proxy HyperdataAny) parent <- getNodeWith r (Proxy :: Proxy HyperdataAny)
let mParent = _node_parentId parent let mParent = _node_parent_id parent
case mParent of case mParent of
Nothing -> pure [] Nothing -> pure []
Just parentId -> do Just parentId -> do
......
...@@ -121,13 +121,13 @@ selectRoot (UserName username) = proc () -> do ...@@ -121,13 +121,13 @@ selectRoot (UserName username) = proc () -> do
users <- queryUserTable -< () users <- queryUserTable -< ()
restrict -< _node_typename row .== (pgInt4 $ toDBid NodeUser) restrict -< _node_typename row .== (pgInt4 $ toDBid NodeUser)
restrict -< user_username users .== (pgStrictText username) restrict -< user_username users .== (pgStrictText username)
restrict -< _node_userId row .== (user_id users) restrict -< _node_user_id row .== (user_id users)
returnA -< row returnA -< row
selectRoot (UserDBId uid) = proc () -> do selectRoot (UserDBId uid) = proc () -> do
row <- queryNodeTable -< () row <- queryNodeTable -< ()
restrict -< _node_typename row .== (pgInt4 $ toDBid NodeUser) restrict -< _node_typename row .== (pgInt4 $ toDBid NodeUser)
restrict -< _node_userId row .== (pgInt4 uid) restrict -< _node_user_id row .== (pgInt4 uid)
returnA -< row returnA -< row
selectRoot (RootId nid) = selectRoot (RootId nid) =
......
...@@ -28,8 +28,8 @@ import Prelude hiding (null, id, map, sum) ...@@ -28,8 +28,8 @@ import Prelude hiding (null, id, map, sum)
data NodePoly id data NodePoly id
hash_id hash_id
typename typename
userId user_id
parentId parent_id
name name
date date
hyperdata = hyperdata =
...@@ -37,8 +37,8 @@ data NodePoly id ...@@ -37,8 +37,8 @@ data NodePoly id
, _node_hash_id :: !hash_id , _node_hash_id :: !hash_id
, _node_typename :: !typename , _node_typename :: !typename
, _node_userId :: !userId , _node_user_id :: !user_id
, _node_parentId :: !parentId , _node_parent_id :: !parent_id
, _node_name :: !name , _node_name :: !name
, _node_date :: !date , _node_date :: !date
...@@ -58,9 +58,9 @@ nodeTable :: Table NodeWrite NodeRead ...@@ -58,9 +58,9 @@ nodeTable :: Table NodeWrite NodeRead
nodeTable = Table "nodes" (pNode Node { _node_id = optional "id" nodeTable = Table "nodes" (pNode Node { _node_id = optional "id"
, _node_hash_id = optional "hash_id" , _node_hash_id = optional "hash_id"
, _node_typename = required "typename" , _node_typename = required "typename"
, _node_userId = required "user_id" , _node_user_id = required "user_id"
, _node_parentId = optional "parent_id" , _node_parent_id = optional "parent_id"
, _node_name = required "name" , _node_name = required "name"
, _node_date = optional "date" , _node_date = optional "date"
...@@ -146,11 +146,11 @@ data NodePolySearch id ...@@ -146,11 +146,11 @@ data NodePolySearch id
search = search =
NodeSearch { _ns_id :: id NodeSearch { _ns_id :: id
, _ns_typename :: typename , _ns_typename :: typename
, _ns_userId :: userId , _ns_user_id :: user_id
-- , nodeUniqId :: shaId -- , nodeUniqId :: shaId
, _ns_parentId :: parentId , _ns_parent_id :: parent_id
, _ns_name :: name , _ns_name :: name
, _ns_date :: date , _ns_date :: date
, _ns_hyperdata :: hyperdata , _ns_hyperdata :: hyperdata
, _ns_search :: search , _ns_search :: search
...@@ -165,9 +165,9 @@ nodeTableSearch :: Table NodeSearchWrite NodeSearchRead ...@@ -165,9 +165,9 @@ nodeTableSearch :: Table NodeSearchWrite NodeSearchRead
nodeTableSearch = Table "nodes" ( pNodeSearch nodeTableSearch = Table "nodes" ( pNodeSearch
NodeSearch { _ns_id = optional "id" NodeSearch { _ns_id = optional "id"
, _ns_typename = required "typename" , _ns_typename = required "typename"
, _ns_userId = required "user_id" , _ns_user_id = required "user_id"
, _ns_parentId = required "parent_id" , _ns_parent_id = required "parent_id"
, _ns_name = required "name" , _ns_name = required "name"
, _ns_date = optional "date" , _ns_date = optional "date"
......
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