Commit 056eb027 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[DB] Favorite and Trash queries: ok.

parent 1b90c03a
......@@ -88,9 +88,11 @@ mkCmd :: (Connection -> IO a) -> Cmd a
mkCmd = Cmd . ReaderT
------------------------------------------------------------------------
type CorpusId = Int
type CorpusId = Int
type AnnuaireId = Int
type UserId = NodeId
type DocId = Int
type UserId = Int
type TypeId = Int
------------------------------------------------------------------------
instance FromField HyperdataCorpus where
......
......@@ -11,11 +11,12 @@ Add Documents/Contact to a Corpus/Annuaire.
-}
------------------------------------------------------------------------
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
------------------------------------------------------------------------
module Gargantext.Database.Node.Document.Add where
......@@ -30,7 +31,6 @@ import Database.PostgreSQL.Simple.ToRow (ToRow(..))
import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..))
import Data.Text (Text)
import qualified Data.Text as DT (pack)
import Gargantext.Database.Node (mkCmd, Cmd(..))
import Gargantext.Database.Types.Node
......@@ -57,7 +57,7 @@ add_debug pId ns = mkCmd $ \c -> formatQuery c queryAdd (Only $ Values fields in
-- | Input Tables: types of the tables
inputSqlTypes :: [Text]
inputSqlTypes = map DT.pack ["int4","int4","bool","bool"]
inputSqlTypes = ["int4","int4","bool","bool"]
-- | SQL query to add documents
-- TODO return id of added documents only
......
......@@ -16,18 +16,21 @@ commentary with @some markup@.
{-# LANGUAGE Arrows #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.NodeNode where
import Gargantext.Database.Node (Cmd(..), mkCmd)
import Gargantext.Prelude
import qualified Database.PostgreSQL.Simple as PGS (Connection, Query, query, Only(..))
import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..))
import Database.PostgreSQL.Simple.SqlQQ (sql)
import Control.Lens.TH (makeLensesWith, abbreviatedFields)
import Data.Maybe (Maybe)
import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import Control.Lens.TH (makeLensesWith, abbreviatedFields)
import Gargantext.Database.Node (Cmd(..), mkCmd, CorpusId, DocId)
import Gargantext.Prelude
import Opaleye
......@@ -90,6 +93,66 @@ instance QueryRunnerColumnDefault PGBool (Maybe Bool) where
queryRunnerColumnDefault = fieldQueryRunnerColumn
------------------------------------------------------------------------
-- | Favorite management
nodeToFavorite :: PGS.Connection -> CorpusId -> DocId -> Bool -> IO [PGS.Only Int]
nodeToFavorite c cId dId b = PGS.query c favQuery (b,cId,dId)
where
favQuery :: PGS.Query
favQuery = [sql|UPDATE nodes_nodes SET favorite = ?
WHERE node1_id = ? AND node2_id = ?
RETURNING node2_id;
|]
nodesToFavorite :: PGS.Connection -> [(CorpusId,DocId,Bool)] -> IO [PGS.Only Int]
nodesToFavorite c inputData = PGS.query c trashQuery (PGS.Only $ Values fields inputData)
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
|]
------------------------------------------------------------------------
------------------------------------------------------------------------
-- | Trash management
nodeToTrash :: PGS.Connection -> CorpusId -> DocId -> Bool -> IO [PGS.Only Int]
nodeToTrash c cId dId b = PGS.query c trashQuery (b,cId,dId)
where
trashQuery :: PGS.Query
trashQuery = [sql|UPDATE nodes_nodes SET delete = ?
WHERE node1_id = ? AND node2_id = ?
RETURNING node2_id
|]
-- | Trash Massive
nodesToTrash :: PGS.Connection -> [(CorpusId,DocId,Bool)] -> IO [PGS.Only Int]
nodesToTrash c inputData = PGS.query c trashQuery (PGS.Only $ Values fields inputData)
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
emptyTrash :: PGS.Connection -> CorpusId -> IO [PGS.Only Int]
emptyTrash c cId = PGS.query c delQuery (PGS.Only cId)
where
delQuery :: PGS.Query
delQuery = [sql|DELETE from nodes_nodes n
WHERE n.node1_id = ?
AND n.delete = true
RETURNING n.node2_id
|]
------------------------------------------------------------------------
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment