Commit 32f76c93 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] Adding Graph type for the REST api.

parent 03f5859a
......@@ -29,6 +29,7 @@ library:
- Gargantext.Text.Search
- Gargantext.Text.Parsers.CSV
- Gargantext.API
- Gargantext.Viz.Graph.Distances.Matrice
dependencies:
- QuickCheck
- accelerate
......
{-|
Module : Gargantext.Viz.Graph
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
module Gargantext.Viz.Graph
where
import GHC.Generics (Generic)
import Data.Aeson.TH (deriveJSON)
import Data.Text (Text)
import Gargantext.Prelude
import Gargantext.Core.Utils.Prefix (unPrefix)
-----------------------------------------------------------
data TypeNode = Terms | Unknown
deriving (Show, Generic)
$(deriveJSON (unPrefix "") ''TypeNode)
data Attributes = Attributes { clust_default :: Int }
deriving (Show, Generic)
$(deriveJSON (unPrefix "") ''Attributes)
data Node = Node { n_size :: Int
, n_type :: TypeNode
, n_id :: Text
, n_label :: Text
, n_attributes :: Attributes
}
deriving (Show, Generic)
$(deriveJSON (unPrefix "n_") ''Node)
data Edge = Edge { e_source :: Int
, e_target :: Int
, e_weight :: Double
, e_id :: Int
}
deriving (Show, Generic)
$(deriveJSON (unPrefix "e_") ''Edge)
data Graph = Graph { g_nodes :: [Node]
, g_edges :: [Edge]
}
deriving (Show, Generic)
$(deriveJSON (unPrefix "g_") ''Graph)
-----------------------------------------------------------
......@@ -14,7 +14,7 @@ Motivation and definition of the @Conditional@ distance.
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE Strict #-}
module Gargantext.Graph.Distances.Conditional
module Gargantext.Viz.Graph.Distances.Conditional
where
import Data.Matrix hiding (identity)
......@@ -33,7 +33,7 @@ import Data.Vector (Vector)
import qualified Data.Vector as V
import Gargantext.Prelude
import Gargantext.Graph.Utils
import Gargantext.Viz.Graph.Utils
------------------------------------------------------------------------
------------------------------------------------------------------------
......
......@@ -16,7 +16,7 @@ Motivation and definition of the @Distributional@ distance.
{-# LANGUAGE Strict #-}
module Gargantext.Graph.Distances.Distributional
module Gargantext.Viz.Graph.Distances.Distributional
where
import Data.Matrix hiding (identity)
......@@ -32,7 +32,7 @@ import Data.Vector (Vector)
import qualified Data.Vector as V
import Gargantext.Prelude
import Gargantext.Graph.Utils
import Gargantext.Viz.Graph.Utils
distributional :: (Floating a, Ord a) => Matrix a -> [((Int, Int), a)]
......
......@@ -14,7 +14,7 @@ Motivation and definition of the @Conditional@ distance.
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
module Gargantext.Graph.Distances.Matrice
module Gargantext.Viz.Graph.Distances.Matrice
where
import Data.Array.Accelerate.Data.Bits
......@@ -77,6 +77,9 @@ conditional m = (run $ ie (use m), run $ sg (use m))
n :: Exp Double
n = P.fromIntegral r
--miniMax m = fold minimum $ fold maximum m
......
......@@ -14,7 +14,7 @@ Portability : POSIX
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE Strict #-}
module Gargantext.Graph.Utils
module Gargantext.Viz.Graph.Utils
where
import Data.Matrix hiding (identity)
......
......@@ -3,7 +3,7 @@ extra-package-dbs: []
packages:
- .
- servant-job
#- '/home/alexandre/local/logiciels/haskell/accelerate/accelerate'
#- '/home/alexandre/local/logiciels/haskell/myCode/louvain'
allow-newer: true
extra-deps:
......
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