]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Database/Schema/NodeNodeNgrams2.hs
max cliques with apax to 2
[gargantext.git] / src / Gargantext / Database / Schema / NodeNodeNgrams2.hs
1 {-|
2 Module : Gargantext.Database.Schema.NodeNodeNgrams
3 Description : TODO: remove this module and table in 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 {-# OPTIONS_GHC -fno-warn-orphans #-}
13
14 {-# LANGUAGE Arrows #-}
15 {-# LANGUAGE FlexibleInstances #-}
16 {-# LANGUAGE FunctionalDependencies #-}
17 {-# LANGUAGE MultiParamTypeClasses #-}
18 {-# LANGUAGE NoImplicitPrelude #-}
19 {-# LANGUAGE RankNTypes #-}
20 {-# LANGUAGE TemplateHaskell #-}
21
22 module Gargantext.Database.Schema.NodeNodeNgrams2
23 where
24
25 import Prelude
26 import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
27 import Control.Lens.TH (makeLenses)
28 import Gargantext.Database.Utils (Cmd, mkCmd)
29 import Gargantext.Database.Schema.NodeNgrams (NodeNgramsId)
30 import Gargantext.Database.Schema.Node (pgNodeId)
31 import Gargantext.Database.Types.Node
32 import Opaleye
33
34 data NodeNodeNgrams2Poly node_id nodengrams_id w
35 = NodeNodeNgrams2 { _nnng2_node_id :: node_id
36 , _nnng2_nodengrams_id :: nodengrams_id
37 , _nnng2_weight :: w
38 } deriving (Show)
39
40 type NodeNodeNgrams2Write =
41 NodeNodeNgrams2Poly (Column PGInt4 )
42 (Column PGInt4 )
43 (Column PGFloat8)
44
45 type NodeNodeNgrams2Read =
46 NodeNodeNgrams2Poly (Column PGInt4 )
47 (Column PGInt4 )
48 (Column PGFloat8)
49
50 type NodeNodeNgrams2ReadNull =
51 NodeNodeNgrams2Poly (Column (Nullable PGInt4 ))
52 (Column (Nullable PGInt4 ))
53 (Column (Nullable PGFloat8))
54
55 type NodeNodeNgrams2 =
56 NodeNodeNgrams2Poly DocId NodeNgramsId Double
57
58 $(makeAdaptorAndInstance "pNodeNodeNgrams2" ''NodeNodeNgrams2Poly)
59 makeLenses ''NodeNodeNgrams2Poly
60
61
62 nodeNodeNgrams2Table :: Table NodeNodeNgrams2Write NodeNodeNgrams2Read
63 nodeNodeNgrams2Table = Table "node_node_ngrams2"
64 ( pNodeNodeNgrams2 NodeNodeNgrams2
65 { _nnng2_node_id = required "node_id"
66 , _nnng2_nodengrams_id = required "nodengrams_id"
67 , _nnng2_weight = required "weight"
68 }
69 )
70
71 queryNodeNodeNgrams2Table :: Query NodeNodeNgrams2Read
72 queryNodeNodeNgrams2Table = queryTable nodeNodeNgrams2Table
73
74 -- | Insert utils
75 insertNodeNodeNgrams2 :: [NodeNodeNgrams2] -> Cmd err Int
76 insertNodeNodeNgrams2 = insertNodeNodeNgrams2W
77 . map (\(NodeNodeNgrams2 n1 n2 w) ->
78 NodeNodeNgrams2 (pgNodeId n1)
79 (pgInt4 n2)
80 (pgDouble w)
81 )
82
83 insertNodeNodeNgrams2W :: [NodeNodeNgrams2Write] -> Cmd err Int
84 insertNodeNodeNgrams2W nnnw =
85 mkCmd $ \c -> fromIntegral <$> runInsert_ c insertNothing
86 where
87 insertNothing = (Insert { iTable = nodeNodeNgrams2Table
88 , iRows = nnnw
89 , iReturning = rCount
90 , iOnConflict = (Just DoNothing)
91 })