]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Database/Action/Query/Ngrams.hs
[DB|WIP] fix Tree RootId
[gargantext.git] / src / Gargantext / Database / Action / Query / Ngrams.hs
1 {-|
2 Module : Gargantext.Database.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.Action.Query.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
25 import Gargantext.Database.Admin.Types.Node (pgNodeId)
26 import Gargantext.Database.Admin.Utils (runOpaQuery, Cmd)
27 import Gargantext.Database.Schema.Ngrams
28 import Gargantext.Database.Schema.Node
29 import Gargantext.Database.Schema.NodeNodeNgrams
30 import Gargantext.Prelude
31 import Opaleye
32
33 selectNgramsByDoc :: [ListId] -> DocId -> NgramsType -> Cmd err [Text]
34 selectNgramsByDoc lIds dId nt = runOpaQuery (query lIds dId nt)
35 where
36
37 join :: Query (NgramsRead, NodeNodeNgramsReadNull)
38 join = leftJoin queryNgramsTable queryNodeNodeNgramsTable on1
39 where
40 on1 (ng,nnng) = ng^.ngrams_id .== nnng^.nnng_ngrams_id
41
42 query cIds' dId' nt' = proc () -> do
43 (ng,nnng) <- join -< ()
44 restrict -< foldl (\b cId -> ((toNullable $ pgNodeId cId) .== nnng^.nnng_node1_id) .|| b) (pgBool True) cIds'
45 restrict -< (toNullable $ pgNodeId dId') .== nnng^.nnng_node2_id
46 restrict -< (toNullable $ pgNgramsType nt') .== nnng^.nnng_ngramsType
47 returnA -< ng^.ngrams_terms
48
49
50 postNgrams :: CorpusId -> DocId -> [Text] -> Cmd err Int
51 postNgrams = undefined
52