]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Database/Query/Table/Ngrams.hs
[DB/REFACT] intermediary step
[gargantext.git] / src / Gargantext / Database / Query / Table / Ngrams.hs
1 {-|
2 Module : Gargantext.Database.Query.Table.Ngrams
3 Description : Deal with in Gargantext Database.
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 Arrows #-}
13 {-# LANGUAGE NoImplicitPrelude #-}
14 {-# LANGUAGE FlexibleContexts #-}
15 {-# LANGUAGE RankNTypes #-}
16
17 module Gargantext.Database.Query.Table.Ngrams
18 where
19
20 import Control.Arrow (returnA)
21 import Control.Lens ((^.))
22 import Data.Text (Text)
23 import Gargantext.Core.Types
24 import Gargantext.Database.Admin.Types.Node (pgNodeId)
25 import Gargantext.Database.Admin.Utils (runOpaQuery, Cmd)
26 import Gargantext.Database.Schema.Ngrams
27 import Gargantext.Database.Schema.NodeNodeNgrams
28 import Gargantext.Prelude
29 import Opaleye
30
31 selectNgramsByDoc :: [ListId] -> DocId -> NgramsType -> Cmd err [Text]
32 selectNgramsByDoc lIds dId nt = runOpaQuery (query lIds dId nt)
33 where
34
35 join :: Query (NgramsRead, NodeNodeNgramsReadNull)
36 join = leftJoin queryNgramsTable queryNodeNodeNgramsTable on1
37 where
38 on1 (ng,nnng) = ng^.ngrams_id .== nnng^.nnng_ngrams_id
39
40 query cIds' dId' nt' = proc () -> do
41 (ng,nnng) <- join -< ()
42 restrict -< foldl (\b cId -> ((toNullable $ pgNodeId cId) .== nnng^.nnng_node1_id) .|| b) (pgBool True) cIds'
43 restrict -< (toNullable $ pgNodeId dId') .== nnng^.nnng_node2_id
44 restrict -< (toNullable $ pgNgramsType nt') .== nnng^.nnng_ngramsType
45 returnA -< ng^.ngrams_terms
46
47
48 postNgrams :: CorpusId -> DocId -> [Text] -> Cmd err Int
49 postNgrams = undefined
50