]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Database/NodeNode.hs
[TAB] Opaleye query for Document view (todo: date + title later).
[gargantext.git] / src / Gargantext / Database / NodeNode.hs
1 {-|
2 Module : Gargantext.Database.NodeNode
3 Description :
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 Here is a longer description of this module, containing some
11 commentary with @some markup@.
12 -}
13
14 {-# OPTIONS_GHC -fno-warn-orphans #-}
15
16 {-# LANGUAGE Arrows #-}
17 {-# LANGUAGE FlexibleInstances #-}
18 {-# LANGUAGE FunctionalDependencies #-}
19 {-# LANGUAGE MultiParamTypeClasses #-}
20 {-# LANGUAGE NoImplicitPrelude #-}
21 {-# LANGUAGE TemplateHaskell #-}
22
23 module Gargantext.Database.NodeNode where
24
25 import Gargantext.Database.Node (Cmd(..), mkCmd)
26 import Gargantext.Prelude
27 import Data.Maybe (Maybe)
28 import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
29 import Control.Lens.TH (makeLensesWith, abbreviatedFields)
30 import qualified Database.PostgreSQL.Simple as PGS
31
32 import Opaleye
33
34
35 data NodeNodePoly node1_id node2_id score fav del
36 = NodeNode { nodeNode_node1_id :: node1_id
37 , nodeNode_node2_id :: node2_id
38 , nodeNode_score :: score
39 , nodeNode_favorite :: fav
40 , nodeNode_delete :: del
41 } deriving (Show)
42
43 type NodeNodeWrite = NodeNodePoly (Column (PGInt4))
44 (Column (PGInt4))
45 (Maybe (Column (PGFloat8)))
46 (Maybe (Column (PGBool)))
47 (Maybe (Column (PGBool)))
48
49 type NodeNodeRead = NodeNodePoly (Column (PGInt4))
50 (Column (PGInt4))
51 (Column (PGFloat8))
52 (Column (PGBool))
53 (Column (PGBool))
54
55 type NodeNodeReadNull = NodeNodePoly (Column (Nullable PGInt4))
56 (Column (Nullable PGInt4))
57 (Column (Nullable PGFloat8))
58 (Column (Nullable PGBool))
59 (Column (Nullable PGBool))
60
61 type NodeNode = NodeNodePoly Int Int (Maybe Double) (Maybe Bool) (Maybe Bool)
62
63 $(makeAdaptorAndInstance "pNodeNode" ''NodeNodePoly)
64 $(makeLensesWith abbreviatedFields ''NodeNodePoly)
65
66 nodeNodeTable :: Table NodeNodeWrite NodeNodeRead
67 nodeNodeTable = Table "nodes_nodes" (pNodeNode
68 NodeNode { nodeNode_node1_id = required "node1_id"
69 , nodeNode_node2_id = required "node2_id"
70 , nodeNode_score = optional "score"
71 , nodeNode_favorite = optional "favorite"
72 , nodeNode_delete = optional "delete"
73 }
74 )
75
76 queryNodeNodeTable :: Query NodeNodeRead
77 queryNodeNodeTable = queryTable nodeNodeTable
78
79
80 -- | not optimized (get all ngrams without filters)
81 nodesNodes :: Cmd [NodeNode]
82 nodesNodes = mkCmd $ \c -> runQuery c queryNodeNodeTable
83
84 instance QueryRunnerColumnDefault (Nullable PGInt4) Int where
85 queryRunnerColumnDefault = fieldQueryRunnerColumn
86
87 instance QueryRunnerColumnDefault PGFloat8 (Maybe Double) where
88 queryRunnerColumnDefault = fieldQueryRunnerColumn
89
90 instance QueryRunnerColumnDefault PGBool (Maybe Bool) where
91 queryRunnerColumnDefault = fieldQueryRunnerColumn
92
93
94
95
96