]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Database/Flow/Utils.hs
[WIP] Connecting graph.
[gargantext.git] / src / Gargantext / Database / Flow / Utils.hs
1 {-|
2 Module : Gargantext.Database.Flow.Utils
3 Description : Database Flow
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 -}
11
12 {-# LANGUAGE NoImplicitPrelude #-}
13 {-# LANGUAGE OverloadedStrings #-}
14 {-# LANGUAGE RankNTypes #-}
15
16 module Gargantext.Database.Flow.Utils
17 where
18
19 import Data.Map (Map)
20 import qualified Data.Map as DM
21 import Gargantext.Prelude
22 import Gargantext.Database.Schema.Ngrams
23 import Gargantext.Database.Types.Node (NodeId, Node, NodePoly(..), Hyperdata)
24 import Gargantext.Database.Utils (Cmd)
25 import Gargantext.Database.Schema.NodeNgram
26 import Gargantext.Core.Types.Main (ListType(..), listTypeId)
27
28 toMaps :: Hyperdata a => (a -> Map (NgramsT Ngrams) Int) -> [Node a] -> Map (NgramsT Ngrams) (Map NodeId Int)
29 toMaps fun ns = mapNodeIdNgrams $ documentIdWithNgrams fun ns'
30 where
31 ns' = map (\(Node nId _ _ _ _ _ json) -> DocumentWithId nId json) ns
32
33 mapNodeIdNgrams :: Hyperdata a => [DocumentIdWithNgrams a] -> Map (NgramsT Ngrams) (Map NodeId Int)
34 mapNodeIdNgrams ds = DM.map (DM.fromListWith (+)) $ DM.fromListWith (<>) xs
35 where
36 xs = [(ng, [(nId, i)]) | (nId, n2i') <- n2i ds, (ng, i) <- DM.toList n2i']
37 n2i = map (\d -> ((documentId . documentWithId) d, document_ngrams d))
38
39
40 documentIdWithNgrams :: Hyperdata a => (a -> Map (NgramsT Ngrams) Int)
41 -> [DocumentWithId a] -> [DocumentIdWithNgrams a]
42 documentIdWithNgrams f = map (\d -> DocumentIdWithNgrams d ((f . documentData) d))
43
44
45 data DocumentWithId a =
46 DocumentWithId { documentId :: NodeId
47 , documentData :: a
48 } deriving (Show)
49
50
51 data DocumentIdWithNgrams a =
52 DocumentIdWithNgrams
53 { documentWithId :: DocumentWithId a
54 , document_ngrams :: Map (NgramsT Ngrams) Int
55 } deriving (Show)
56
57 -- | TODO for now, list Type is CandidateList because Graph Terms
58 -- have to be detected in next step in the flow
59 insertToNodeNgrams :: Map NgramsIndexed (Map NgramsType (Map NodeId Int)) -> Cmd err Int
60 insertToNodeNgrams m = insertNodeNgrams [ NodeNgram n (_ngramsId ng) Nothing (ngramsTypeId t) (listTypeId CandidateList) (fromIntegral i)
61 | (ng, t2n2i) <- DM.toList m
62 , (t, n2i) <- DM.toList t2n2i
63 , (n, i) <- DM.toList n2i
64 ]
65