Commit 422f0ca4 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[GRAPH] Sorting the nodes.

parent 3d6fbdb3
......@@ -254,10 +254,10 @@ viewDocuments :: CorpusId -> Trash -> NodeTypeId -> Query FacetDocRead
viewDocuments cId t ntId = proc () -> do
n <- queryNodeTable -< ()
nn <- queryNodeNodeTable -< ()
restrict -< _node_id n .== nn_node2_id nn
restrict -< nn_node1_id nn .== (pgNodeId cId)
restrict -< _node_typename n .== (pgInt4 ntId)
restrict -< nn_delete nn .== (pgBool t)
restrict -< _node_id n .== nn_node2_id nn
restrict -< nn_node1_id nn .== (pgNodeId cId)
restrict -< _node_typename n .== (pgInt4 ntId)
restrict -< nn_delete nn .== (pgBool t)
returnA -< FacetDoc (_node_id n) (_node_date n) (_node_name n) (_node_hyperdata n) (nn_favorite nn) (pgInt4 1)
......
......@@ -164,7 +164,7 @@ flowCorpusUser l userName corpusName ctype ids = do
--}
-- User Dashboard Flow
-- _ <- mkDashboard userCorpusId userId
_ <- mkDashboard userCorpusId userId
-- Annuaire Flow
-- _ <- mkAnnuaire rootUserId userId
......
......@@ -22,16 +22,17 @@ Portability : POSIX
module Gargantext.Viz.Graph.API
where
import Control.Lens (set)
import Data.List (sortOn)
import Control.Lens (set, view)
import Control.Monad.IO.Class (liftIO)
import Gargantext.API.Ngrams.Tools
import Gargantext.API.Types
import Gargantext.Core.Types.Main
import Gargantext.Database.Metrics.NgramsByNode (getNodesByNgramsOnlyUser)
import Gargantext.Database.Schema.Ngrams
import Gargantext.Database.Schema.Node ( getNode)
import Gargantext.Database.Schema.Node (getNode)
import Gargantext.Database.Schema.Node (defaultList)
import Gargantext.Database.Types.Node -- (GraphId, ListId, CorpusId, NodeId)
import Gargantext.Database.Types.Node hiding (node_id) -- (GraphId, ListId, CorpusId, NodeId)
import Gargantext.Prelude
import Gargantext.Viz.Graph
import Gargantext.Viz.Graph.Tools -- (cooc2graph)
......@@ -72,7 +73,11 @@ getGraph nId = do
<$> groupNodesByNgrams ngs
<$> getNodesByNgramsOnlyUser cId NgramsTerms (Map.keys ngs)
liftIO $ set graph_metadata (Just metadata) <$> cooc2graph myCooc
graph <- liftIO $ cooc2graph myCooc
pure $ set graph_metadata (Just metadata)
$ set graph_nodes ( sortOn node_id
$ view graph_nodes graph
) graph
postGraph :: NodeId -> GargServer (Post '[JSON] [NodeId])
......
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