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

Merge remote-tracking branch 'origin/475-dev-node-team-invite' into dev-merge

parents 331ffc70 d27f9ebd
...@@ -132,6 +132,7 @@ library ...@@ -132,6 +132,7 @@ library
Gargantext.API.GraphQL.Utils Gargantext.API.GraphQL.Utils
Gargantext.API.Job Gargantext.API.Job
Gargantext.API.Metrics Gargantext.API.Metrics
Gargantext.API.Members
Gargantext.API.Ngrams.List Gargantext.API.Ngrams.List
Gargantext.API.Ngrams.List.Types Gargantext.API.Ngrams.List.Types
Gargantext.API.Ngrams.NgramsTree Gargantext.API.Ngrams.NgramsTree
......
module Gargantext.API.Members where
import Gargantext.Prelude
import Gargantext.API.Prelude
import Servant
import Data.Text (Text)
import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.Core.Types (UserId)
import Gargantext.Database.Admin.Types.Node (NodeType(NodeTeam))
import Gargantext.Database.Query.Table.Node (getNodesIdWithType)
import Gargantext.Database.Action.Share (membersOf)
import Gargantext.Database.Prelude (HasConnectionPool, HasConfig)
import Gargantext.Core.Mail.Types (HasMail)
import Control.Monad.Extra (concatMapM)
type MembersAPI = Get '[JSON] [Text]
members :: UserId -> ServerT MembersAPI (GargM Env GargError)
members _ = do
getMembers
getMembers :: (HasConnectionPool env, HasConfig env, HasMail env) => GargM env GargError [Text]
getMembers = do
teamNodeIds <- getNodesIdWithType NodeTeam
m <- concatMapM membersOf teamNodeIds
pure $ map fst m
...@@ -33,6 +33,7 @@ import Gargantext.API.Admin.EnvTypes (Env, GargJob(..)) ...@@ -33,6 +33,7 @@ import Gargantext.API.Admin.EnvTypes (Env, GargJob(..))
import Gargantext.API.Admin.FrontEnd (FrontEndAPI) import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
import Gargantext.API.Context import Gargantext.API.Context
import Gargantext.API.Count (CountAPI, count, Query) import Gargantext.API.Count (CountAPI, count, Query)
import Gargantext.API.Members (MembersAPI, members)
import Gargantext.API.Job (jobLogInit) import Gargantext.API.Job (jobLogInit)
import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc) import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
import Gargantext.API.Node import Gargantext.API.Node
...@@ -163,6 +164,9 @@ type GargPrivateAPI' = ...@@ -163,6 +164,9 @@ type GargPrivateAPI' =
:> Capture "tree_id" NodeId :> Capture "tree_id" NodeId
:> TreeAPI :> TreeAPI
:<|> "members" :> Summary "Team node members"
:> MembersAPI
-- :<|> New.Upload -- :<|> New.Upload
:<|> New.AddWithForm :<|> New.AddWithForm
-- :<|> New.AddWithFile -- :<|> New.AddWithFile
...@@ -248,6 +252,8 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid)) ...@@ -248,6 +252,8 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
:<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
<$> PathNode <*> treeAPI <$> PathNode <*> treeAPI
:<|> members uid
-- TODO access -- TODO access
:<|> addCorpusWithForm (RootId (NodeId uid)) :<|> addCorpusWithForm (RootId (NodeId uid))
-- :<|> addCorpusWithFile (RootId (NodeId uid)) -- :<|> addCorpusWithFile (RootId (NodeId uid))
......
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