2 Module : Gargantext.Viz.Graph
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# LANGUAGE NoImplicitPrelude #-}
13 {-# LANGUAGE TemplateHaskell #-}
14 {-# LANGUAGE DeriveGeneric #-}
16 module Gargantext.Viz.Graph
19 import GHC.IO (FilePath)
20 import GHC.Generics (Generic)
21 import Data.Aeson.TH (deriveJSON)
22 import qualified Data.Aeson as DA
24 import Data.ByteString.Lazy as DBL (readFile, writeFile)
26 import Data.Text (Text)
27 import qualified Text.Read as T
28 import qualified Data.Text as T
32 import Gargantext.Prelude
33 import Gargantext.Core.Utils.Prefix (unPrefix)
35 import Data.Graph.Clustering.Louvain.CplusPlus (LouvainNode)
38 data TypeNode = Terms | Unknown
39 deriving (Show, Generic)
41 $(deriveJSON (unPrefix "") ''TypeNode)
43 data Attributes = Attributes { clust_default :: Int }
44 deriving (Show, Generic)
45 $(deriveJSON (unPrefix "") ''Attributes)
47 data Node = Node { node_size :: Int
48 , node_type :: TypeNode
51 , node_attributes :: Attributes
53 deriving (Show, Generic)
54 $(deriveJSON (unPrefix "node_") ''Node)
56 data Edge = Edge { edge_source :: Text
58 , edge_weight :: Double
61 deriving (Show, Generic)
62 $(deriveJSON (unPrefix "edge_") ''Edge)
64 data Graph = Graph { graph_nodes :: [Node]
65 , graph_edges :: [Edge]
67 deriving (Show, Generic)
68 $(deriveJSON (unPrefix "graph_") ''Graph)
69 -----------------------------------------------------------
70 -- Old Gargantext Version
72 data AttributesOld = AttributesOld { cl :: Int }
73 deriving (Show, Generic)
74 $(deriveJSON (unPrefix "") ''AttributesOld)
76 data NodeOld = NodeOld { no_id :: Int
77 , no_at :: AttributesOld
81 deriving (Show, Generic)
82 $(deriveJSON (unPrefix "no_") ''NodeOld)
84 data EdgeOld = EdgeOld { eo_s :: Int
88 deriving (Show, Generic)
89 $(deriveJSON (unPrefix "eo_") ''EdgeOld)
91 data GraphOld = GraphOld {
93 , go_nodes :: [NodeOld]
95 deriving (Show, Generic)
96 $(deriveJSON (unPrefix "go_") ''GraphOld)
98 ----------------------------------------------------------
101 graphOld2graph :: GraphOld -> Graph
102 graphOld2graph (GraphOld links nodes) = Graph (map nodeOld2node nodes) (zipWith linkOld2edge [1..] links)
104 nodeOld2node :: NodeOld -> Node
105 nodeOld2node (NodeOld no_id' (AttributesOld cl') no_s' no_lb')
106 = Node no_s' Terms (cs $ show no_id') no_lb' (Attributes cl')
108 linkOld2edge :: Int -> EdgeOld -> Edge
109 linkOld2edge n (EdgeOld eo_s' eo_t' eo_w') = Edge (cs $ show eo_s') (cs $ show eo_t') ((T.read $ T.unpack eo_w') :: Double) (cs $ show n)
112 graphOld2graphWithFiles :: FilePath -> FilePath -> IO ()
113 graphOld2graphWithFiles g1 g2 = do
114 -- GraphOld <- IO Fichier
115 graph <- DBL.readFile g1
116 let newGraph = case DA.decode graph :: Maybe GraphOld of
117 Nothing -> panic (T.pack "no graph")
120 DBL.writeFile g2 (DA.encode $ graphOld2graph newGraph)