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

[FIX] Get default lists of userMaster.

parent 4a7eac85
...@@ -34,7 +34,7 @@ add get ...@@ -34,7 +34,7 @@ add get
module Gargantext.API.Ngrams module Gargantext.API.Ngrams
where where
--import Debug.Trace (trace) import Debug.Trace (trace)
import Prelude (Enum, Bounded, Semigroup(..), minBound, maxBound {-, round-}, error) import Prelude (Enum, Bounded, Semigroup(..), minBound, maxBound {-, round-}, error)
-- import Gargantext.Database.Schema.User (UserId) -- import Gargantext.Database.Schema.User (UserId)
import Data.Functor (($>)) import Data.Functor (($>))
...@@ -47,7 +47,7 @@ import Data.Monoid ...@@ -47,7 +47,7 @@ import Data.Monoid
--import Data.Semigroup --import Data.Semigroup
import Data.Set (Set) import Data.Set (Set)
-- import qualified Data.List as List -- import qualified Data.List as List
-- import Data.Maybe (isJust) import Data.Maybe (catMaybes)
-- import Data.Tuple.Extra (first) -- import Data.Tuple.Extra (first)
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import Data.Map.Strict (Map) import Data.Map.Strict (Map)
...@@ -70,8 +70,11 @@ import Data.Validity ...@@ -70,8 +70,11 @@ import Data.Validity
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
-- import Gargantext.Database.Schema.Ngrams (NgramsTypeId, ngramsTypeId, NgramsTableData(..)) -- import Gargantext.Database.Schema.Ngrams (NgramsTypeId, ngramsTypeId, NgramsTableData(..))
import Gargantext.Database.Config (userMaster)
import Gargantext.Database.Schema.Ngrams (NgramsType) import Gargantext.Database.Schema.Ngrams (NgramsType)
import Gargantext.Database.Utils (fromField') import Gargantext.Database.Utils (fromField', HasConnection)
import Gargantext.Database.Lists (listsWith)
import Gargantext.Database.Schema.Node (HasNodeError)
import Database.PostgreSQL.Simple.FromField (FromField, fromField) import Database.PostgreSQL.Simple.FromField (FromField, fromField)
import qualified Gargantext.Database.Schema.Ngrams as Ngrams import qualified Gargantext.Database.Schema.Ngrams as Ngrams
-- import Gargantext.Database.Schema.NodeNgram hiding (Action) -- import Gargantext.Database.Schema.NodeNgram hiding (Action)
...@@ -744,7 +747,7 @@ getListNgrams nodeIds ngramsType = do ...@@ -744,7 +747,7 @@ getListNgrams nodeIds ngramsType = do
-- | TODO Errors management -- | TODO Errors management
-- TODO: polymorphic for Annuaire or Corpus or ... -- TODO: polymorphic for Annuaire or Corpus or ...
-- | Table of Ngrams is a ListNgrams formatted (sorted and/or cut). -- | Table of Ngrams is a ListNgrams formatted (sorted and/or cut).
getTableNgrams :: RepoCmdM env err m getTableNgrams :: (RepoCmdM env err m, HasNodeError err, HasConnection env)
=> CorpusId -> Maybe TabType => CorpusId -> Maybe TabType
-> [ListId] -> Maybe Limit -> Maybe Offset -> [ListId] -> Maybe Limit -> Maybe Offset
-- -> Maybe MinSize -> Maybe MaxSize -- -> Maybe MinSize -> Maybe MaxSize
...@@ -758,7 +761,8 @@ getTableNgrams _cId maybeTabType listIds mlimit moffset = do ...@@ -758,7 +761,8 @@ getTableNgrams _cId maybeTabType listIds mlimit moffset = do
defaultLimit = 10 -- TODO defaultLimit = 10 -- TODO
limit_ = maybe defaultLimit identity mlimit limit_ = maybe defaultLimit identity mlimit
offset_ = maybe 0 identity moffset offset_ = maybe 0 identity moffset
getListNgrams ([104] <> listIds) ngramsType lists <- catMaybes <$> listsWith userMaster
trace (show lists) $ getListNgrams (lists <> listIds) ngramsType
& mapped . v_data . _NgramsTable %~ (take limit_ . drop offset_) & mapped . v_data . _NgramsTable %~ (take limit_ . drop offset_)
{-|
Module : Gargantext.Database.Lists
Description : Main requests of Node to the database
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE Arrows #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.Lists where
import Control.Arrow (returnA)
import Gargantext.Core.Types -- (NodePoly(..), NodeCorpus, ListId)
import Gargantext.Core.Types.Individu (Username)
import Gargantext.Database.Config (nodeTypeId)
import Gargantext.Database.Schema.Node -- (HasNodeError, queryNodeTable)
import Gargantext.Database.Schema.User -- (queryUserTable)
import Gargantext.Database.Utils
import Gargantext.Prelude hiding (sum, head)
import Opaleye hiding (FromField)
import Opaleye.Internal.QueryArr (Query)
import Prelude hiding (null, id, map, sum)
-- | To get all lists of a user
-- /!\ lists of different types of corpora (Annuaire or Documents)
listsWith :: HasNodeError err => Username -> Cmd err [Maybe ListId]
listsWith u = runOpaQuery (selectLists u)
where
selectLists u = proc () -> do
(auth_user,nodes) <- listsWithJoin2 -< ()
restrict -< user_username auth_user .== (pgStrictText u)
restrict -< _node_typename nodes .== (toNullable $ pgInt4 $ nodeTypeId NodeList)
returnA -< _node_id nodes
listsWithJoin2 :: Query (UserRead, NodeReadNull)
listsWithJoin2 = leftJoin queryUserTable queryNodeTable cond12
where
cond12 (u,n) = user_id u .== _node_userId n
{-
listsWithJoin3 :: Query (NodeRead, (UserRead, NodeReadNull))
listsWithJoin3 = leftJoin3 queryUserTable queryNodeTable queryNodeTable cond12 cond23
where
cond12 :: (NodeRead
cond12 (u,n) = user_id u .== _node_userId n
cond23 :: (NodeRead, (UserRead, NodeReadNull)) -> Column PGBool
cond23 (n1,(u,n2)) = (toNullable $ _node_id n1) .== _node_parentId n2
--}
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