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
12 {-# OPTIONS_GHC -fno-warn-orphans #-}
14 {-# LANGUAGE Arrows #-}
15 {-# LANGUAGE FlexibleContexts #-}
16 {-# LANGUAGE FlexibleInstances #-}
17 {-# LANGUAGE FunctionalDependencies #-}
18 {-# LANGUAGE MultiParamTypeClasses #-}
19 {-# LANGUAGE NoImplicitPrelude #-}
20 {-# LANGUAGE RankNTypes #-}
21 {-# LANGUAGE TemplateHaskell #-}
23 module Gargantext.Database.Schema.NodeNodeNgrams2
27 import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
28 import Control.Lens.TH (makeLenses)
29 import Gargantext.Database.Utils (Cmd, mkCmd)
30 import Gargantext.Database.Schema.NodeNgrams (NodeNgramsId)
31 import Gargantext.Database.Schema.Node (pgNodeId)
32 import Gargantext.Database.Types.Node
35 data NodeNodeNgrams2Poly node_id nodengrams_id w
36 = NodeNodeNgrams2 { _nnng2_node_id :: node_id
37 , _nnng2_nodengrams_id :: nodengrams_id
41 type NodeNodeNgrams2Write =
42 NodeNodeNgrams2Poly (Column PGInt4 )
46 type NodeNodeNgrams2Read =
47 NodeNodeNgrams2Poly (Column PGInt4 )
51 type NodeNodeNgrams2ReadNull =
52 NodeNodeNgrams2Poly (Column (Nullable PGInt4 ))
53 (Column (Nullable PGInt4 ))
54 (Column (Nullable PGFloat8))
56 type NodeNodeNgrams2 =
57 NodeNodeNgrams2Poly DocId NodeNgramsId Double
59 $(makeAdaptorAndInstance "pNodeNodeNgrams2" ''NodeNodeNgrams2Poly)
60 makeLenses ''NodeNodeNgrams2Poly
63 nodeNodeNgrams2Table :: Table NodeNodeNgrams2Write NodeNodeNgrams2Read
64 nodeNodeNgrams2Table = Table "node_node_ngrams2"
65 ( pNodeNodeNgrams2 NodeNodeNgrams2
66 { _nnng2_node_id = required "node_id"
67 , _nnng2_nodengrams_id = required "nodengrams_id"
68 , _nnng2_weight = required "weight"
72 queryNodeNodeNgrams2Table :: Query NodeNodeNgrams2Read
73 queryNodeNodeNgrams2Table = queryTable nodeNodeNgrams2Table
76 insertNodeNodeNgrams2 :: [NodeNodeNgrams2] -> Cmd err Int
77 insertNodeNodeNgrams2 = insertNodeNodeNgrams2W
78 . map (\(NodeNodeNgrams2 n1 n2 w) ->
79 NodeNodeNgrams2 (pgNodeId n1)
84 insertNodeNodeNgrams2W :: [NodeNodeNgrams2Write] -> Cmd err Int
85 insertNodeNodeNgrams2W nnnw =
86 mkCmd $ \c -> fromIntegral <$> runInsert_ c insertNothing
88 insertNothing = (Insert { iTable = nodeNodeNgrams2Table
91 , iOnConflict = (Just DoNothing)