NodeNode.hs 7.58 KB
Newer Older
1
{-|
2
Module      : Gargantext.Database.Schema.NodeNode
3 4 5 6 7 8 9 10 11 12 13
Description : 
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX

Here is a longer description of this module, containing some
commentary with @some markup@.
-}

14 15
{-# OPTIONS_GHC -fno-warn-orphans #-}

16 17 18
{-# LANGUAGE Arrows                 #-}
{-# LANGUAGE FlexibleInstances      #-}
{-# LANGUAGE FunctionalDependencies #-}
19
{-# LANGUAGE QuasiQuotes            #-}
20 21
{-# LANGUAGE MultiParamTypeClasses  #-}
{-# LANGUAGE NoImplicitPrelude      #-}
Alexandre Delanoë's avatar
Alexandre Delanoë committed
22
{-# LANGUAGE OverloadedStrings      #-}
23
{-# LANGUAGE RankNTypes             #-}
24 25
{-# LANGUAGE TemplateHaskell        #-}

26
module Gargantext.Database.Schema.NodeNode where
27

28
import Control.Lens (view)
29
import qualified Database.PostgreSQL.Simple as PGS (Query, Only(..))
30 31 32
import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..))
import Database.PostgreSQL.Simple.SqlQQ (sql)
import Control.Lens.TH (makeLensesWith, abbreviatedFields)
33 34
import Data.Maybe (Maybe, catMaybes)
import Data.Text (Text, splitOn)
35
import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
36 37
import Gargantext.Database.Schema.Node 
import Gargantext.Core.Types
38
import Gargantext.Database.Utils
39
import Gargantext.Database.Config (nodeTypeId)
40
import Gargantext.Database.Types.Node (CorpusId, DocId)
41
import Gargantext.Prelude
42
import Opaleye
43 44
import Control.Arrow (returnA)
import qualified Opaleye as O
45

46
data NodeNodePoly node1_id node2_id score fav del
47 48 49 50 51
                   = NodeNode { nn_node1_id   :: node1_id
                              , nn_node2_id   :: node2_id
                              , nn_score :: score
                              , nn_favorite :: fav
                              , nn_delete   :: del
52 53
                              } deriving (Show)

54 55 56 57 58 59 60 61 62 63 64 65 66 67
type NodeNodeWrite     = NodeNodePoly (Column (PGInt4))
                                      (Column (PGInt4))
                                      (Maybe  (Column (PGFloat8)))
                                      (Maybe  (Column (PGBool)))
                                      (Maybe  (Column (PGBool)))

type NodeNodeRead      = NodeNodePoly (Column (PGInt4))
                                      (Column (PGInt4))
                                      (Column (PGFloat8))
                                      (Column (PGBool))
                                      (Column (PGBool))
                                      
type NodeNodeReadNull  = NodeNodePoly (Column (Nullable PGInt4))
                                      (Column (Nullable PGInt4))
Alexandre Delanoë's avatar
Alexandre Delanoë committed
68
                                      (Column (Nullable PGFloat8))
69 70
                                      (Column (Nullable PGBool))
                                      (Column (Nullable PGBool))
71

72
type NodeNode = NodeNodePoly Int Int (Maybe Double) (Maybe Bool) (Maybe Bool)
73 74 75 76

$(makeAdaptorAndInstance "pNodeNode" ''NodeNodePoly)
$(makeLensesWith abbreviatedFields   ''NodeNodePoly)

77 78
nodeNodeTable :: Table NodeNodeWrite NodeNodeRead
nodeNodeTable  = Table "nodes_nodes" (pNodeNode
79 80 81 82 83
                                NodeNode { nn_node1_id = required "node1_id"
                                         , nn_node2_id = required "node2_id"
                                         , nn_score    = optional "score"
                                         , nn_favorite = optional "favorite"
                                         , nn_delete   = optional "delete"
Alexandre Delanoë's avatar
Alexandre Delanoë committed
84 85
                                     }
                                     )
86 87 88 89 90 91

queryNodeNodeTable :: Query NodeNodeRead
queryNodeNodeTable = queryTable nodeNodeTable


-- | not optimized (get all ngrams without filters)
92 93
nodesNodes :: Cmd err [NodeNode]
nodesNodes = runOpaQuery queryNodeNodeTable
94

95 96 97
instance QueryRunnerColumnDefault (Nullable PGInt4) Int where
    queryRunnerColumnDefault = fieldQueryRunnerColumn

98 99
instance QueryRunnerColumnDefault PGFloat8 (Maybe Double) where
    queryRunnerColumnDefault = fieldQueryRunnerColumn
100

101 102 103 104
instance QueryRunnerColumnDefault PGBool (Maybe Bool) where
    queryRunnerColumnDefault = fieldQueryRunnerColumn


105 106
------------------------------------------------------------------------
-- | Favorite management
107 108
nodeToFavorite :: CorpusId -> DocId -> Bool -> Cmd err [Int]
nodeToFavorite cId dId b = map (\(PGS.Only a) -> a) <$> runPGSQuery favQuery (b,cId,dId)
109 110 111 112 113 114 115
  where
    favQuery :: PGS.Query
    favQuery = [sql|UPDATE nodes_nodes SET favorite = ?
               WHERE node1_id = ? AND node2_id = ?
               RETURNING node2_id;
               |]

116 117 118
nodesToFavorite :: [(CorpusId,DocId,Bool)] -> Cmd err [Int]
nodesToFavorite inputData = map (\(PGS.Only a) -> a)
                            <$> runPGSQuery trashQuery (PGS.Only $ Values fields inputData)
119 120 121 122 123 124 125 126 127 128 129 130
  where
    fields = map (\t-> QualifiedIdentifier Nothing t) ["int4","int4","bool"]
    trashQuery :: PGS.Query
    trashQuery = [sql| UPDATE nodes_nodes as old SET
                 favorite = new.favorite
                 from (?) as new(node1_id,node2_id,favorite)
                 WHERE old.node1_id = new.node1_id
                 AND   old.node2_id = new.node2_id
                 RETURNING new.node2_id
                  |]

------------------------------------------------------------------------
131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158
-- | TODO use UTCTime fast 
selectDocsDates :: CorpusId -> Cmd err [Text]
selectDocsDates cId = 
                map (head' "selectDocsDates" . splitOn "-")
               <$> catMaybes
               <$> map (view hyperdataDocument_publication_date)
               <$> selectDocs cId


selectDocs :: CorpusId -> Cmd err [HyperdataDocument]
selectDocs cId = runOpaQuery (queryDocs cId)

queryDocs :: CorpusId -> O.Query (Column PGJsonb)
queryDocs cId = proc () -> do
  (n, nn) <- joinInCorpus -< ()
  restrict -< ( nn_node1_id nn)  .== (toNullable $ pgNodeId cId)
  restrict -< ( nn_delete nn)    .== (toNullable $ pgBool False)
  restrict -< (_node_typename n) .== (pgInt4 $ nodeTypeId NodeDocument)
  returnA -< view (node_hyperdata) n


joinInCorpus :: O.Query (NodeRead, NodeNodeReadNull)
joinInCorpus = leftJoin queryNodeTable queryNodeNodeTable cond
  where
    cond :: (NodeRead, NodeNodeRead) -> Column PGBool
    cond (n, nn) = nn_node2_id nn .== (view node_id n)


159 160
------------------------------------------------------------------------
-- | Trash management
161 162
nodeToTrash :: CorpusId -> DocId -> Bool -> Cmd err [PGS.Only Int]
nodeToTrash cId dId b = runPGSQuery trashQuery (b,cId,dId)
163 164 165 166 167 168 169 170
  where
    trashQuery :: PGS.Query
    trashQuery = [sql|UPDATE nodes_nodes SET delete = ?
                  WHERE node1_id = ? AND node2_id = ?
                  RETURNING node2_id
                  |]

-- | Trash Massive
171 172 173
nodesToTrash :: [(CorpusId,DocId,Bool)] -> Cmd err [Int]
nodesToTrash input = map (\(PGS.Only a) -> a)
                        <$> runPGSQuery trashQuery (PGS.Only $ Values fields input)
174 175 176 177 178 179 180 181 182 183 184 185
  where
    fields = map (\t-> QualifiedIdentifier Nothing t) ["int4","int4","bool"]
    trashQuery :: PGS.Query
    trashQuery = [sql| UPDATE nodes_nodes as old SET
                 delete = new.delete
                 from (?) as new(node1_id,node2_id,delete)
                 WHERE old.node1_id = new.node1_id
                 AND   old.node2_id = new.node2_id
                 RETURNING new.node2_id
                  |]

-- | /!\ Really remove nodes in the Corpus or Annuaire
186 187
emptyTrash :: CorpusId -> Cmd err [PGS.Only Int]
emptyTrash cId = runPGSQuery delQuery (PGS.Only cId)
188 189 190 191 192 193 194 195
  where
    delQuery :: PGS.Query
    delQuery = [sql|DELETE from nodes_nodes n
                    WHERE n.node1_id = ?
                      AND n.delete = true
                    RETURNING n.node2_id
                |]
------------------------------------------------------------------------