]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Database/Schema/NodeNodeNgrams.hs
[DATABASE] Postgres upgrade + schema + triggers (use gargantext-init to configure...
[gargantext.git] / src / Gargantext / Database / Schema / NodeNodeNgrams.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.NodeNodeNgrams
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.Ngrams (NgramsTypeId, pgNgramsTypeId, NgramsId)
30 import Gargantext.Database.Schema.Node (pgNodeId)
31 import Gargantext.Database.Types.Node
32 import Opaleye
33
34
35
36 data NodeNodeNgramsPoly n1 n2 ngrams_id ngt w
37 = NodeNodeNgrams { _nnng_node1_id :: n1
38 , _nnng_node2_id :: n2
39 , _nnng_ngrams_id :: ngrams_id
40 , _nnng_ngramsType :: ngt
41 , _nnng_weight :: w
42 } deriving (Show)
43
44
45 type NodeNodeNgramsWrite =
46 NodeNodeNgramsPoly (Column PGInt4 )
47 (Column PGInt4 )
48 (Column PGInt4 )
49 (Column PGInt4 )
50 (Column PGFloat8)
51
52 type NodeNodeNgramsRead =
53 NodeNodeNgramsPoly (Column PGInt4 )
54 (Column PGInt4 )
55 (Column PGInt4 )
56 (Column PGInt4 )
57 (Column PGFloat8)
58
59 type NodeNodeNgramsReadNull =
60 NodeNodeNgramsPoly (Column (Nullable PGInt4 ))
61 (Column (Nullable PGInt4 ))
62 (Column (Nullable PGInt4 ))
63 (Column (Nullable PGInt4 ))
64 (Column (Nullable PGFloat8))
65
66 type NodeNodeNgrams =
67 NodeNodeNgramsPoly CorpusId DocId NgramsId NgramsTypeId Double
68
69 $(makeAdaptorAndInstance "pNodeNodeNgrams" ''NodeNodeNgramsPoly)
70 makeLenses ''NodeNodeNgramsPoly
71
72
73 nodeNodeNgramsTable :: Table NodeNodeNgramsWrite NodeNodeNgramsRead
74 nodeNodeNgramsTable = Table "node_node_ngrams"
75 ( pNodeNodeNgrams NodeNodeNgrams
76 { _nnng_node1_id = required "node1_id"
77 , _nnng_node2_id = required "node2_id"
78 , _nnng_ngrams_id = required "ngrams_id"
79 , _nnng_ngramsType = required "ngrams_type"
80 , _nnng_weight = required "weight"
81 }
82 )
83
84 queryNodeNodeNgramsTable :: Query NodeNodeNgramsRead
85 queryNodeNodeNgramsTable = queryTable nodeNodeNgramsTable
86
87
88 -- | Insert utils
89 insertNodeNodeNgrams :: [NodeNodeNgrams] -> Cmd err Int
90 insertNodeNodeNgrams = insertNodeNodeNgramsW
91 . map (\(NodeNodeNgrams n1 n2 ng nt w) ->
92 NodeNodeNgrams (pgNodeId n1)
93 (pgNodeId n2)
94 (pgInt4 ng)
95 (pgNgramsTypeId nt)
96 (pgDouble w)
97 )
98
99 insertNodeNodeNgramsW :: [NodeNodeNgramsWrite] -> Cmd err Int
100 insertNodeNodeNgramsW nnnw =
101 mkCmd $ \c -> fromIntegral <$> runInsert_ c insertNothing
102 where
103 insertNothing = (Insert { iTable = nodeNodeNgramsTable
104 , iRows = nnnw
105 , iReturning = rCount
106 , iOnConflict = (Just DoNothing)
107 })
108
109