2 Module : Gargantext.API.Node.Corpus.Export
3 Description : Get Metrics from Storage (Database like)
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 Main exports of Gargantext:
16 {-# LANGUAGE TemplateHaskell #-}
17 {-# LANGUAGE TypeOperators #-}
18 {-# OPTIONS_GHC -fno-warn-orphans #-}
20 module Gargantext.API.Node.Corpus.Export
24 import Data.Aeson.TH (deriveJSON)
26 import Data.Maybe (fromMaybe)
29 import Data.Text (Text)
30 import GHC.Generics (Generic)
31 import Gargantext.API.Ngrams
32 import Gargantext.API.Ngrams.Tools (filterListWithRoot, mapTermListRoot, getRepo)
33 import Gargantext.API.Prelude (GargNoServer)
34 import Gargantext.Prelude.Crypto.Hash (hash)
35 import Gargantext.Core.Types
36 import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
37 import Gargantext.Database.Action.Metrics.NgramsByNode (getNgramsByNodeOnlyUser)
38 import Gargantext.Database.Admin.Config (userMaster)
39 import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..))
40 import Gargantext.Database.Prelude (Cmd)
41 import Gargantext.Database.Query.Table.Node
42 import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
43 import Gargantext.Database.Query.Table.Node.Select (selectNodesWithUsername)
44 import Gargantext.Database.Query.Table.NodeNode (selectDocNodes)
45 import Gargantext.Database.Schema.Ngrams (NgramsType(..))
46 import Gargantext.Database.Schema.Node (_node_id, _node_hyperdata)
47 import Gargantext.Prelude
49 import qualified Data.List as List
50 import qualified Data.Map as Map
51 import qualified Data.Set as Set
56 Corpus { _c_corpus :: [Document]
62 Document { _d_document :: Node HyperdataDocument
68 Ngrams { _ng_ngrams :: [Text]
74 instance ToSchema Corpus where
75 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_c_")
77 instance ToSchema Document where
78 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_d_")
80 instance ToSchema Ngrams where
81 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_ng_")
83 instance (ToSchema a) => ToSchema (Node a) where
84 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_node_")
87 instance ToParamSchema Corpus where
88 toParamSchema _ = toParamSchema (Proxy :: Proxy TODO)
90 instance ToParamSchema Document where
91 toParamSchema _ = toParamSchema (Proxy :: Proxy TODO)
93 instance ToParamSchema Ngrams where
94 toParamSchema _ = toParamSchema (Proxy :: Proxy TODO)
95 --------------------------------------------------
96 type API = Summary "Corpus Export"
98 :> QueryParam "listId" ListId
99 :> QueryParam "ngramsType" NgramsType
100 :> Get '[JSON] Corpus
102 --------------------------------------------------
103 -- | Hashes are ordered by Set
104 getCorpus :: CorpusId
107 -> GargNoServer Corpus
108 getCorpus cId lId nt' = do
112 Nothing -> NgramsTerms
116 <$> map (\n -> (_node_id n, n))
117 <$> selectDocNodes cId
119 ngs <- getNodeNgrams cId lId nt repo
120 let -- uniqId is hash computed already for each document imported in database
121 r = Map.intersectionWith (\a b -> Document a (Ngrams (Set.toList b) (hash b)) (d_hash a b)
124 d_hash a b = hash [ fromMaybe "" (_hd_uniqId $ _node_hyperdata a)
127 pure $ Corpus (Map.elems r) (hash $ List.map _d_hash
131 getNodeNgrams :: HasNodeError err
136 -> Cmd err (Map NodeId (Set Text))
137 getNodeNgrams cId lId' nt repo = do
139 Nothing -> defaultList cId
142 lIds <- selectNodesWithUsername NodeList userMaster
143 let ngs = filterListWithRoot MapTerm $ mapTermListRoot [lId] nt repo
144 r <- getNgramsByNodeOnlyUser cId (lIds <> [lId]) nt (Map.keys ngs)
148 $(deriveJSON (unPrefix "_c_") ''Corpus)
149 $(deriveJSON (unPrefix "_d_") ''Document)
150 $(deriveJSON (unPrefix "_ng_") ''Ngrams)
155 -- Version number of the list