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