Commit f578cd68 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[DB/FACT] fix warnings

parent db05a1d4
......@@ -127,7 +127,7 @@ import Gargantext.Core.Types (TODO)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Action.Metrics.NgramsByNode (getOccByNgramsOnlyFast')
import Gargantext.Database.Query.Table.Node.Select
import Gargantext.Database.Query.Table.Ngrams hiding (NgramsType(..))
import Gargantext.Database.Query.Table.Ngrams hiding (NgramsType(..), ngrams, ngramsType, ngrams_terms)
import Gargantext.Database.Admin.Config (userMaster)
import Gargantext.Database.Admin.Types.Errors (HasNodeError)
import Gargantext.Database.Admin.Types.Node (NodeType(..))
......
......@@ -59,7 +59,6 @@ import Gargantext.Database.Query.Join (leftJoin5)
import Gargantext.Database.Query.Table.Ngrams
import Gargantext.Database.Admin.Config (nodeTypeId)
import Gargantext.Database.Admin.Utils
import Gargantext.Database.Schema.Ngrams
import Gargantext.Database.Schema.Node
import Gargantext.Database.Query.Table.NodeNode
import Gargantext.Database.Query.Table.NodeNodeNgrams
......
......@@ -10,11 +10,12 @@ Portability : POSIX
-}
{-# LANGUAGE Arrows #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
module Gargantext.Database.Query.Table.Ngrams
( module Gargantext.Database.Schema.Ngrams
......@@ -27,18 +28,17 @@ module Gargantext.Database.Query.Table.Ngrams
import Control.Arrow (returnA)
import Control.Lens ((^.))
import Data.Text (Text)
import Data.Map (Map, fromList, lookup)
import Data.Map (Map, fromList)
import Gargantext.Core.Types
import Gargantext.Database.Admin.Types.Node (pgNodeId)
import Gargantext.Database.Admin.Utils (runOpaQuery, Cmd)
import Gargantext.Database.Schema.Ngrams
import Gargantext.Database.Admin.Utils (Cmd, runPGSQuery, runOpaQuery, formatPGSQuery)
import Gargantext.Database.Admin.Utils (runPGSQuery, formatPGSQuery)
import Gargantext.Database.Query.Table.NodeNodeNgrams
import Gargantext.Prelude
import Gargantext.Database.Schema.Prelude
import Data.ByteString.Internal (ByteString)
import qualified Database.PostgreSQL.Simple as PGS
import Opaleye
queryNgramsTable :: Query NgramsRead
queryNgramsTable = queryTable ngramsTable
......@@ -60,11 +60,11 @@ selectNgramsByDoc lIds dId nt = runOpaQuery (query lIds dId nt)
returnA -< ng^.ngrams_terms
postNgrams :: CorpusId -> DocId -> [Text] -> Cmd err Int
postNgrams = undefined
_postNgrams :: CorpusId -> DocId -> [Text] -> Cmd err Int
_postNgrams = undefined
dbGetNgramsDb :: Cmd err [NgramsDb]
dbGetNgramsDb = runOpaQuery queryNgramsTable
_dbGetNgramsDb :: Cmd err [NgramsDb]
_dbGetNgramsDb = runOpaQuery queryNgramsTable
-- TODO-ACCESS: access must not be checked here but when insertNgrams is called.
......@@ -77,8 +77,8 @@ insertNgrams' ns = runPGSQuery queryInsertNgrams (PGS.Only $ Values fields ns)
where
fields = map (\t -> QualifiedIdentifier Nothing t) ["text", "int4"]
insertNgrams_Debug :: [(NgramsTerms, Size)] -> Cmd err ByteString
insertNgrams_Debug ns = formatPGSQuery queryInsertNgrams (PGS.Only $ Values fields ns)
_insertNgrams_Debug :: [(NgramsTerms, Size)] -> Cmd err ByteString
_insertNgrams_Debug ns = formatPGSQuery queryInsertNgrams (PGS.Only $ Values fields ns)
where
fields = map (\t -> QualifiedIdentifier Nothing t) ["text", "int4"]
......
......@@ -30,7 +30,6 @@ import Gargantext.Database.Admin.Config (nodeTypeId)
import Gargantext.Database.Admin.Types.Node (pgNodeId)
import Gargantext.Database.Admin.Utils
import Gargantext.Database.Schema.Node
import Gargantext.Database.Schema.NodeNode
import Opaleye
getAllDocuments :: ParentId -> Cmd err (TableResult (Node HyperdataDocument))
......
......@@ -59,8 +59,8 @@ queryNodeNodeTable :: Query NodeNodeRead
queryNodeNodeTable = queryTable nodeNodeTable
-- | not optimized (get all ngrams without filters)
nodesNodes :: Cmd err [NodeNode]
nodesNodes = runOpaQuery queryNodeNodeTable
_nodesNodes :: Cmd err [NodeNode]
_nodesNodes = runOpaQuery queryNodeNodeTable
------------------------------------------------------------------------
-- | Basic NodeNode tools
......@@ -87,8 +87,8 @@ insertNodeNode ns = mkCmd $ \conn -> runInsert_ conn $ Insert nodeNodeTable ns'
-- | Favorite management
nodeNodeCategory :: CorpusId -> DocId -> Int -> Cmd err [Int]
nodeNodeCategory cId dId c = map (\(PGS.Only a) -> a) <$> runPGSQuery favQuery (c,cId,dId)
_nodeNodeCategory :: CorpusId -> DocId -> Int -> Cmd err [Int]
_nodeNodeCategory cId dId c = map (\(PGS.Only a) -> a) <$> runPGSQuery favQuery (c,cId,dId)
where
favQuery :: PGS.Query
favQuery = [sql|UPDATE nodes_nodes SET category = ?
......@@ -146,40 +146,3 @@ joinInCorpus = leftJoin queryNodeTable queryNodeNodeTable cond
cond :: (NodeRead, NodeNodeRead) -> Column PGBool
cond (n, nn) = nn^.nn_node2_id .== (view node_id n)
------------------------------------------------------------------------
-- | Trash management
nodeToTrash :: CorpusId -> DocId -> Bool -> Cmd err [PGS.Only Int]
nodeToTrash cId dId b = runPGSQuery 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 :: [(CorpusId,DocId,Bool)] -> Cmd err [Int]
nodesToTrash input = map (\(PGS.Only a) -> a)
<$> runPGSQuery trashQuery (PGS.Only $ Values fields input)
where
fields = map (\t-> QualifiedIdentifier Nothing t) ["int4","int4","bool"]
trashQuery :: PGS.Query
trashQuery = [sql| UPDATE nodes_nodes as nn0 SET
delete = nn1.delete
from (?) as nn1(node1_id,node2_id,delete)
WHERE nn0.node1_id = nn1.node1_id
AND nn0.node2_id = nn1.node2_id
RETURNING nn1.node2_id
|]
-- | /!\ Really remove nodes in the Corpus or Annuaire
emptyTrash :: CorpusId -> Cmd err [PGS.Only Int]
emptyTrash cId = runPGSQuery 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
|]
------------------------------------------------------------------------
......@@ -27,13 +27,12 @@ module Gargantext.Database.Query.Table.NodeNodeNgrams
)
where
import Prelude
import Gargantext.Database.Admin.Types.Node (pgNodeId)
import Gargantext.Database.Admin.Utils (Cmd, mkCmd)
import Gargantext.Database.Schema.Prelude
import Gargantext.Database.Schema.Ngrams (NgramsTypeId, pgNgramsTypeId, NgramsId)
import Gargantext.Database.Schema.Ngrams (pgNgramsTypeId)
import Gargantext.Database.Schema.NodeNodeNgrams
import Gargantext.Database.Admin.Types.Node (pgNodeId)
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Schema.Prelude
import Prelude
queryNodeNodeNgramsTable :: Query NodeNodeNgramsRead
......
......@@ -33,8 +33,8 @@ import Gargantext.Database.Admin.Utils (Cmd, mkCmd)
import Prelude
queryNodeNodeNgrams2Table :: Query NodeNodeNgrams2Read
queryNodeNodeNgrams2Table = queryTable nodeNodeNgrams2Table
_queryNodeNodeNgrams2Table :: Query NodeNodeNgrams2Read
_queryNodeNodeNgrams2Table = queryTable nodeNodeNgrams2Table
-- | Insert utils
insertNodeNodeNgrams2 :: [NodeNodeNgrams2] -> Cmd err Int
......
......@@ -40,11 +40,9 @@ module Gargantext.Database.Query.Table.Node_NodeNgramsNodeNgrams
)
where
import Control.Lens.TH (makeLensesWith, abbreviatedFields)
import Data.Maybe (Maybe)
import Gargantext.Database.Schema.Prelude
import Gargantext.Database.Admin.Utils (Cmd, runOpaQuery, mkCmd)
import Gargantext.Database.Admin.Types.Node (CorpusId, pgNodeId)
import Gargantext.Database.Admin.Types.Node (pgNodeId)
import Gargantext.Database.Schema.Node_NodeNgramsNodeNgrams
import Gargantext.Database.Schema.Node()
import Gargantext.Prelude
......@@ -55,8 +53,8 @@ queryNode_NodeNgrams_NodeNgrams_Table = queryTable node_NodeNgrams_NodeNgrams_Ta
-- | Select NodeNgramsNgrams
-- TODO not optimized (get all ngrams without filters)
node_Node_NodeNgrams_NodeNgrams :: Cmd err [Node_NodeNgrams_NodeNgrams]
node_Node_NodeNgrams_NodeNgrams = runOpaQuery queryNode_NodeNgrams_NodeNgrams_Table
_node_Node_NodeNgrams_NodeNgrams :: Cmd err [Node_NodeNgrams_NodeNgrams]
_node_Node_NodeNgrams_NodeNgrams = runOpaQuery queryNode_NodeNgrams_NodeNgrams_Table
-- TODO: Add option on conflict
......
{-|
Module : Gargantext.Database.Schema.NodesNgramsRepo
Description : NodeNgram for Ngram indexation or Lists
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
......@@ -24,32 +23,28 @@ Portability : POSIX
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.Query.Table.NodesNgramsRepo
( module Gargantext.Database.Schema.NodesNgramsRepo
)
where
import Gargantext.Database.Schema.Prelude
import Gargantext.API.Ngrams (NgramsStatePatch, NgramsTablePatch)
import Gargantext.Database.Schema.Ngrams (NgramsType)
import Gargantext.Database.Admin.Types.Node (NodeId)
import Gargantext.API.Ngrams (NgramsStatePatch)
import Gargantext.Database.Schema.NodesNgramsRepo
import Gargantext.Database.Admin.Utils (mkCmd, Cmd, runOpaQuery)
import Gargantext.Prelude
selectRepo :: Cmd err [RepoDbNgrams]
selectRepo = runOpaQuery selectPatches
selectPatches :: Query RepoDbRead
selectPatches = proc () -> do
repos <- queryTable repoTable -< ()
returnA -< repos
_selectRepo :: Cmd err [RepoDbNgrams]
_selectRepo = runOpaQuery selectPatches
insertRepos :: [NgramsStatePatch] -> Cmd err Int64
insertRepos ns = mkCmd $ \conn -> runInsert_ conn $ Insert repoTable (toWrite ns) rCount Nothing
_insertRepos :: [NgramsStatePatch] -> Cmd err Int64
_insertRepos ns = mkCmd $ \conn -> runInsert_ conn $ Insert repoTable (toWrite ns) rCount Nothing
where
toWrite :: [NgramsStatePatch] -> [RepoDbWrite]
toWrite = undefined
......
......@@ -31,7 +31,6 @@ import Control.Lens (makeLenses, over)
import Control.Monad (mzero)
import Data.Aeson
import Data.Aeson.Types (toJSONKeyText)
import Data.ByteString.Internal (ByteString)
import Data.Map (Map, fromList, lookup)
import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import Data.Swagger (ToParamSchema, toParamSchema, ToSchema)
......
......@@ -25,7 +25,7 @@ module Gargantext.Database.Schema.NodeNodeNgrams
import Prelude
import Gargantext.Database.Schema.Prelude
import Gargantext.Database.Schema.Ngrams (NgramsTypeId, pgNgramsTypeId, NgramsId)
import Gargantext.Database.Schema.Ngrams (NgramsTypeId, NgramsId)
import Gargantext.Database.Admin.Types.Node
data NodeNodeNgramsPoly n1 n2 ngrams_id ngt w
......
......@@ -25,7 +25,6 @@ module Gargantext.Database.Schema.NodeNodeNgrams2
import Gargantext.Database.Schema.Prelude
import Gargantext.Database.Schema.NodeNgrams (NodeNgramsId)
import Gargantext.Database.Admin.Types.Node (pgNodeId)
import Gargantext.Database.Admin.Types.Node
import Prelude
......
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