Commit 7c2cdbd2 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[GRAPH] IGraph types and functions extracted from Proxemy.

parent 4fdd60c6
...@@ -154,6 +154,8 @@ library: ...@@ -154,6 +154,8 @@ library:
- pureMD5 - pureMD5
- SHA - SHA
- simple-reflect - simple-reflect
- cereal # (IGraph)
- singletons # (IGraph)
- random - random
- rake - rake
- regex-compat - regex-compat
......
...@@ -134,7 +134,6 @@ flowCorpusSearchInDatabase' u la q = do ...@@ -134,7 +134,6 @@ flowCorpusSearchInDatabase' u la q = do
ids <- map fst <$> searchInDatabase cId (stemIt q) ids <- map fst <$> searchInDatabase cId (stemIt q)
flowCorpusUser la u q (Nothing :: Maybe HyperdataCorpus) ids flowCorpusUser la u q (Nothing :: Maybe HyperdataCorpus) ids
------------------------------------------------------------------------ ------------------------------------------------------------------------
flow :: (FlowCmdM env ServantErr m, FlowCorpus a, MkCorpus c) flow :: (FlowCmdM env ServantErr m, FlowCorpus a, MkCorpus c)
......
...@@ -14,19 +14,17 @@ Références: ...@@ -14,19 +14,17 @@ Références:
-} -}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Gargantext.Viz.Graph.Proxemy module Gargantext.Viz.Graph.Proxemy
where where
import Gargantext.Prelude import Gargantext.Prelude
import IGraph
import Data.Map (Map) import Data.Map (Map)
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.List as List import qualified Data.List as List
import Gargantext.Viz.Graph.IGraph
type Graph_Undirected = Graph 'U () ()
type Length = Int type Length = Int
type FalseReflexive = Bool type FalseReflexive = Bool
type NeighborsFilter = Graph_Undirected -> Node -> [Node] type NeighborsFilter = Graph_Undirected -> Node -> [Node]
...@@ -104,13 +102,13 @@ spreading g ms r nf = Map.fromListWith (+) $ List.concat $ map pvalue (Map.keys ...@@ -104,13 +102,13 @@ spreading g ms r nf = Map.fromListWith (+) $ List.concat $ map pvalue (Map.keys
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Graph Tools -- | Graph Tools
mkGraphUfromEdges :: [(Int, Int)] -> Graph 'U () () mkGraphUfromEdges :: [(Int, Int)] -> Graph_Undirected
mkGraphUfromEdges es = mkGraph (List.replicate n ()) $ zip es $ repeat () mkGraphUfromEdges es = mkGraph (List.replicate n ()) $ zip es $ repeat ()
where where
(a,b) = List.unzip es (a,b) = List.unzip es
n = List.length (List.nub $ a <> b) n = List.length (List.nub $ a <> b)
mkGraphDfromEdges :: [(Int, Int)] -> Graph 'D () () mkGraphDfromEdges :: [(Int, Int)] -> Graph_Directed
mkGraphDfromEdges = undefined mkGraphDfromEdges = undefined
filterNeighbors :: Graph_Undirected -> Node -> [Node] filterNeighbors :: Graph_Undirected -> Node -> [Node]
...@@ -129,7 +127,7 @@ ecount = fromIntegral . List.length . List.nub . edges ...@@ -129,7 +127,7 @@ ecount = fromIntegral . List.length . List.nub . edges
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Behavior tests -- | Behavior tests
graphTest :: Graph 'U () () graphTest :: Graph_Undirected
graphTest= mkGraphUfromEdges [(0,1),(0,2),(0,4),(0,5),(1,0),(1,3),(1,8),(2,0),(2,3),(2,4),(2,5),(2,6),(2,16),(3,1),(3,2),(3,4),(3,5),(3,6),(3,18),(4,0),(4,2),(4,3),(4,6),(5,0),(5,2),(5,3),(5,8),(6,2),(6,3),(6,4),(7,8),(7,9),(7,10),(7,13),(8,1),(8,5),(8,7),(8,9),(8,10),(8,11),(8,12),(8,13),(9,7),(9,8),(9,12),(9,13),(10,7),(10,8),(10,11),(10,17),(11,8),(11,10),(11,12),(12,8),(12,9),(12,11),(13,7),(13,8),(13,9),(13,20),(14,16),(14,17),(14,18),(14,20),(15,16),(15,17),(15,18),(15,20),(16,2),(16,14),(16,15),(16,18),(16,20),(17,10),(17,14),(17,15),(17,18),(17,20),(18,3),(18,14),(18,15),(18,16),(18,17),(18,19),(18,20),(19,18),(19,20),(20,13),(20,14),(20,15),(20,16),(20,17),(20,18),(20,19)] graphTest= mkGraphUfromEdges [(0,1),(0,2),(0,4),(0,5),(1,0),(1,3),(1,8),(2,0),(2,3),(2,4),(2,5),(2,6),(2,16),(3,1),(3,2),(3,4),(3,5),(3,6),(3,18),(4,0),(4,2),(4,3),(4,6),(5,0),(5,2),(5,3),(5,8),(6,2),(6,3),(6,4),(7,8),(7,9),(7,10),(7,13),(8,1),(8,5),(8,7),(8,9),(8,10),(8,11),(8,12),(8,13),(9,7),(9,8),(9,12),(9,13),(10,7),(10,8),(10,11),(10,17),(11,8),(11,10),(11,12),(12,8),(12,9),(12,11),(13,7),(13,8),(13,9),(13,20),(14,16),(14,17),(14,18),(14,20),(15,16),(15,17),(15,18),(15,20),(16,2),(16,14),(16,15),(16,18),(16,20),(17,10),(17,14),(17,15),(17,18),(17,20),(18,3),(18,14),(18,15),(18,16),(18,17),(18,19),(18,20),(19,18),(19,20),(20,13),(20,14),(20,15),(20,16),(20,17),(20,18),(20,19)]
-- | Tests -- | Tests
......
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