Commit 21e3b7ca authored by Alexandre Delanoë's avatar Alexandre Delanoë

[REST] Adding Graph api end point.

parent 40463188
...@@ -68,6 +68,7 @@ import Gargantext.API.FrontEnd (FrontEndAPI, frontEndServer) ...@@ -68,6 +68,7 @@ import Gargantext.API.FrontEnd (FrontEndAPI, frontEndServer)
import Gargantext.API.Node ( Roots , roots import Gargantext.API.Node ( Roots , roots
, NodeAPI , nodeAPI , NodeAPI , nodeAPI
, NodesAPI , nodesAPI , NodesAPI , nodesAPI
, GraphAPI, graphAPI
) )
import Gargantext.API.Count ( CountAPI, count, Query) import Gargantext.API.Count ( CountAPI, count, Query)
import Gargantext.API.Search ( SearchAPI, search, SearchQuery) import Gargantext.API.Search ( SearchAPI, search, SearchQuery)
...@@ -215,6 +216,9 @@ type GargAPI = ...@@ -215,6 +216,9 @@ type GargAPI =
-- Corpus endpoint -- Corpus endpoint
:<|> "search":> Summary "Search endpoint" :<|> "search":> Summary "Search endpoint"
:> ReqBody '[JSON] SearchQuery :> SearchAPI :> ReqBody '[JSON] SearchQuery :> SearchAPI
:<|> "graph" :> Summary "Graph endpoint"
:> Capture "id" Int :> GraphAPI
-- :<|> "scraper" :> WithCallbacks ScraperAPI -- :<|> "scraper" :> WithCallbacks ScraperAPI
...@@ -242,6 +246,7 @@ server env = do ...@@ -242,6 +246,7 @@ server env = do
:<|> nodesAPI conn :<|> nodesAPI conn
:<|> count :<|> count
:<|> search conn :<|> search conn
:<|> graphAPI conn
-- :<|> orchestrator -- :<|> orchestrator
where where
conn = env ^. env_conn conn = env ^. env_conn
......
...@@ -45,6 +45,11 @@ import Gargantext.Database.Node ( getNodesWithParentId ...@@ -45,6 +45,11 @@ import Gargantext.Database.Node ( getNodesWithParentId
import Gargantext.Database.Facet (FacetDoc, getDocFacet import Gargantext.Database.Facet (FacetDoc, getDocFacet
,FacetChart) ,FacetChart)
-- Graph
import Gargantext.TextFlow
import Gargantext.Viz.Graph (Graph)
import Gargantext.Core (Lang(..))
import Gargantext.Text.Terms (TermType(..))
------------------------------------------------------------------- -------------------------------------------------------------------
------------------------------------------------------------------- -------------------------------------------------------------------
-- | Node API Types management -- | Node API Types management
...@@ -101,6 +106,12 @@ roots conn = liftIO (putStrLn ( "/user" :: Text) >> getNodesWithParentId conn 0 ...@@ -101,6 +106,12 @@ roots conn = liftIO (putStrLn ( "/user" :: Text) >> getNodesWithParentId conn 0
:<|> pure (panic "not implemented yet") :<|> pure (panic "not implemented yet")
:<|> pure (panic "not implemented yet") :<|> pure (panic "not implemented yet")
type GraphAPI = Get '[JSON] Graph
graphAPI :: Connection -> NodeId -> Server GraphAPI
graphAPI _ _ = liftIO $ textFlow (Mono EN) (Contexts contextText)
nodeAPI :: Connection -> NodeId -> Server NodeAPI nodeAPI :: Connection -> NodeId -> Server NodeAPI
nodeAPI conn id = liftIO (putStrLn ("/node" :: Text) >> getNode conn id ) nodeAPI conn id = liftIO (putStrLn ("/node" :: Text) >> getNode conn id )
:<|> deleteNode' conn id :<|> deleteNode' conn id
...@@ -110,6 +121,8 @@ nodeAPI conn id = liftIO (putStrLn ("/node" :: Text) >> getNode co ...@@ -110,6 +121,8 @@ nodeAPI conn id = liftIO (putStrLn ("/node" :: Text) >> getNode co
-- :<|> upload -- :<|> upload
-- :<|> query -- :<|> query
nodesAPI :: Connection -> [NodeId] -> Server NodesAPI nodesAPI :: Connection -> [NodeId] -> Server NodesAPI
nodesAPI conn ids = deleteNodes' conn ids nodesAPI conn ids = deleteNodes' conn ids
......
...@@ -16,6 +16,7 @@ Portability : POSIX ...@@ -16,6 +16,7 @@ Portability : POSIX
module Gargantext.Viz.Graph module Gargantext.Viz.Graph
where where
------------------------------------------------------------------------
import GHC.IO (FilePath) import GHC.IO (FilePath)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
...@@ -23,19 +24,26 @@ import qualified Data.Aeson as DA ...@@ -23,19 +24,26 @@ import qualified Data.Aeson as DA
import Data.ByteString.Lazy as DBL (readFile, writeFile) import Data.ByteString.Lazy as DBL (readFile, writeFile)
import Data.Text (Text) import Data.Text (Text, pack)
import qualified Text.Read as T import qualified Text.Read as T
import qualified Data.Text as T import qualified Data.Text as T
import Data.Map.Strict (Map) import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M import qualified Data.Map.Strict as M
import Data.Swagger (ToSchema)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Types (Label) import Gargantext.Core.Types (Label)
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
import Data.Graph.Clustering.Louvain.CplusPlus (LouvainNode(..)) import Data.Graph.Clustering.Louvain.CplusPlus (LouvainNode(..))
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import Test.QuickCheck (elements)
------------------------------------------------------------------------
data TypeNode = Terms | Unknown data TypeNode = Terms | Unknown
deriving (Show, Generic) deriving (Show, Generic)
...@@ -67,6 +75,19 @@ data Graph = Graph { graph_nodes :: [Node] ...@@ -67,6 +75,19 @@ data Graph = Graph { graph_nodes :: [Node]
} }
deriving (Show, Generic) deriving (Show, Generic)
$(deriveJSON (unPrefix "graph_") ''Graph) $(deriveJSON (unPrefix "graph_") ''Graph)
-- | Intances for Swagger documentation
instance ToSchema Node
instance ToSchema TypeNode
instance ToSchema Attributes
instance ToSchema Edge
instance ToSchema Graph
-- | Intances for the mack
instance Arbitrary Graph where
arbitrary = elements $ [Graph {graph_nodes = [Node {node_size = 4, node_type = Terms, node_id = pack "0", node_label = pack "animal", node_attributes = Attributes {clust_default = 0}},Node {node_size = 3, node_type = Terms, node_id = pack "1", node_label = pack "bird", node_attributes = Attributes {clust_default = 0}},Node {node_size = 2, node_type = Terms, node_id = pack "2", node_label = pack "boy", node_attributes = Attributes {clust_default = 1}},Node {node_size = 2, node_type = Terms, node_id = pack "3", node_label = pack "dog", node_attributes = Attributes {clust_default = 0}},Node {node_size = 2, node_type = Terms, node_id = pack "4", node_label = pack "girl", node_attributes = Attributes {clust_default = 1}},Node {node_size = 4, node_type = Terms, node_id = pack "5", node_label = pack "human body", node_attributes = Attributes {clust_default = 1}},Node {node_size = 3, node_type = Terms, node_id = pack "6", node_label = pack "object", node_attributes = Attributes {clust_default = 2}},Node {node_size = 2, node_type = Terms, node_id = pack "7", node_label = pack "pen", node_attributes = Attributes {clust_default = 2}},Node {node_size = 2, node_type = Terms, node_id = pack "8", node_label = pack "table", node_attributes = Attributes {clust_default = 2}}], graph_edges = [Edge {edge_source = pack "0", edge_target = pack "0", edge_weight = 1.0, edge_id = pack "0"},Edge {edge_source = pack "1", edge_target = pack "0", edge_weight = 1.0, edge_id = pack "1"},Edge {edge_source = pack "1", edge_target = pack "1", edge_weight = 1.0, edge_id = pack "2"},Edge {edge_source = pack "2", edge_target = pack "2", edge_weight = 1.0, edge_id = pack "3"},Edge {edge_source = pack "2", edge_target = pack "5", edge_weight = 1.0, edge_id = pack "4"},Edge {edge_source = pack "3", edge_target = pack "0", edge_weight = 1.0, edge_id = pack "5"},Edge {edge_source = pack "3", edge_target = pack "1", edge_weight = 1.0, edge_id = pack "6"},Edge {edge_source = pack "3", edge_target = pack "3", edge_weight = 1.0, edge_id = pack "7"},Edge {edge_source = pack "4", edge_target = pack "4", edge_weight = 1.0, edge_id = pack "8"},Edge {edge_source = pack "4", edge_target = pack "5", edge_weight = 1.0, edge_id = pack "9"},Edge {edge_source = pack "5", edge_target = pack "5", edge_weight = 1.0, edge_id = pack "10"},Edge {edge_source = pack "6", edge_target = pack "6", edge_weight = 1.0, edge_id = pack "11"},Edge {edge_source = pack "7", edge_target = pack "6", edge_weight = 1.0, edge_id = pack "12"},Edge {edge_source = pack "7", edge_target = pack "7", edge_weight = 1.0, edge_id = pack "13"},Edge {edge_source = pack "8", edge_target = pack "6", edge_weight = 1.0, edge_id = pack "14"},Edge {edge_source = pack "8", edge_target = pack "7", edge_weight = 1.0, edge_id = pack "15"},Edge {edge_source = pack "8", edge_target = pack "8", edge_weight = 1.0, edge_id = pack "16"}]}]
----------------------------------------------------------- -----------------------------------------------------------
-- Old Gargantext Version -- Old Gargantext Version
......
...@@ -117,7 +117,6 @@ matProba r mat = zipWith (/) mat (matSum r mat) ...@@ -117,7 +117,6 @@ matProba r mat = zipWith (/) mat (matSum r mat)
diag :: Elt e => Acc (Matrix e) -> Acc (Vector e) diag :: Elt e => Acc (Matrix e) -> Acc (Vector e)
diag m = backpermute (indexTail (shape m)) (lift1 (\(Z :. x) -> (Z :. x :. (x :: Exp Int)))) m diag m = backpermute (indexTail (shape m)) (lift1 (\(Z :. x) -> (Z :. x :. (x :: Exp Int)))) m
-- | Divide by the Diagonal of the matrix -- | Divide by the Diagonal of the matrix
-- --
-- >>> run $ divByDiag 3 (use $ matrix 3 ([1..] :: [Double])) -- >>> run $ divByDiag 3 (use $ matrix 3 ([1..] :: [Double]))
...@@ -209,21 +208,25 @@ conditional' m = (run $ ie $ map fromIntegral $ use m, run $ sg $ map fromIntegr ...@@ -209,21 +208,25 @@ conditional' m = (run $ ie $ map fromIntegral $ use m, run $ sg $ map fromIntegr
-- Distributional measure is a relative measure which depends on the -- Distributional measure is a relative measure which depends on the
-- selected list, it represents structural equivalence. -- selected list, it represents structural equivalence.
-- --
-- The distributional measure \[P_c\] of @i@ and @j@ terms is: \[ -- The distributional measure P(c) of @i@ and @j@ terms is: \[
-- S_{MI} = \frac {\sum_{k \neq i,j ; MI_{ik} >0}^{} \min(MI_{ik}, -- S_{MI} = \frac {\sum_{k \neq i,j ; MI_{ik} >0}^{} \min(MI_{ik},
-- MI_{jk})}{\sum_{k \neq i,j ; MI_{ik}}^{}} \] -- MI_{jk})}{\sum_{k \neq i,j ; MI_{ik}}^{}} \]
-- --
-- Mutual information -- Mutual information
-- \[S{MI}({i},{j}) = \log(\frac{C{ij}}{E{ij}})\] -- \[S_{MI}({i},{j}) = \log(\frac{C{ij}}{E{ij}})\]
-- --
-- Number of cooccurrences of @i@ and @j@ in the same context of text -- Number of cooccurrences of @i@ and @j@ in the same context of text
-- \[C{ij}\] -- \[C{ij}\]
-- --
-- The expected value of the cooccurrences -- The expected value of the cooccurrences @i@ and @j@ (given a map list of size @n@)
-- \[E_{ij} = \frac {S_{i} S_{j}} {N}\] -- \[E_{ij}^{m} = \frac {S_{i} S_{j}} {N_{m}}\]
--
-- Total cooccurrences of term @i@ given a map list of size @m@
-- \[S_{i} = \sum_{j, j \neq i}^{m} S_{ij}\]
--
-- Total cooccurrences of terms given a map list of size @m@
-- \[N_{m} = \sum_{i,i \neq i}^{m} \sum_{j, j \neq j}^{m} S_{ij}\]
-- --
-- Total cooccurrences of @i@ term
-- \[N_{i} = \sum_{i}^{} S_{i}\]
distributional :: Matrix Int -> Matrix Double distributional :: Matrix Int -> Matrix Double
distributional m = run $ matMiniMax $ ri (map fromIntegral $ use m) distributional m = run $ matMiniMax $ ri (map fromIntegral $ use m)
where where
...@@ -232,17 +235,17 @@ distributional m = run $ matMiniMax $ ri (map fromIntegral $ use m) ...@@ -232,17 +235,17 @@ distributional m = run $ matMiniMax $ ri (map fromIntegral $ use m)
ri mat = zipWith (/) mat1 mat2 ri mat = zipWith (/) mat1 mat2
where where
mat1 = matSum n $ zipWith min (mi mat) (mi $ transpose mat) mat1 = matSum n $ zipWith min (s_mi mat) (s_mi $ transpose mat)
mat2 = matSum n mat mat2 = matSum n mat
mi m' = zipWith (\a b -> max (log $ a/b) 0) m' s_mi m' = zipWith (\a b -> log (a/b)) m'
$ zipWith (/) (crossProduct m') (total m') $ zipWith (/) (crossProduct m') (total m')
total m'' = replicate (constant (Z :. n :. n)) $ fold (+) 0 $ fold (+) 0 m'' total m'' = replicate (constant (Z :. n :. n)) $ fold (+) 0 $ fold (+) 0 m''
n = dim m n = dim m
crossProduct m''' = zipWith (*) (cross m''' ) (cross (transpose m''')) crossProduct m''' = zipWith (*) (cross m''' ) (cross (transpose m'''))
cross mat = zipWith (-) (matSum n mat) (mat) cross mat = zipWith (-) (matSum n mat) (mat)
----------------------------------------------------------------------- -----------------------------------------------------------------------
----------------------------------------------------------------------- -----------------------------------------------------------------------
......
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