Commit 9878c616 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT|COLLAB] share node implemented

parent 9bfb085f
......@@ -81,7 +81,6 @@ import qualified Paths_gargantext as PG -- cabal magic build module
data Mode = Dev | Mock | Prod
deriving (Show, Read, Generic)
-- | startGargantext takes as parameters port number and Ini file.
startGargantext :: Mode -> PortNumber -> FilePath -> IO ()
startGargantext mode port file = do
......@@ -103,7 +102,6 @@ stopGargantext env = do
T.putStrLn "----- Stopping gargantext -----"
runReaderT saveRepo env
-- | Output generated @swagger.json@ file for the @'TodoAPI'@.
swaggerWriteJSON :: IO ()
swaggerWriteJSON = BL8.writeFile "swagger.json" (encodePretty swaggerDoc)
......
......@@ -42,6 +42,7 @@ import Gargantext.API.Metrics
import Gargantext.API.Ngrams (TabType(..), TableNgramsApi, apiNgramsTableCorpus, QueryParamR)
import Gargantext.API.Ngrams.NTree (MyTree)
import Gargantext.API.Node.New
import qualified Gargantext.API.Node.Share as Share
import Gargantext.API.Search (SearchDocsAPI, searchDocs, SearchPairsAPI, searchPairs)
import Gargantext.API.Table
import Gargantext.Core.Types (NodeTableResult)
......@@ -127,6 +128,7 @@ type NodeAPI a = Get '[JSON] (Node a)
:<|> "category" :> CatApi
:<|> "search" :> SearchDocsAPI
:<|> "share" :> Share.API
-- Pairing utilities
:<|> "pairwith" :> PairWith
......@@ -201,6 +203,7 @@ nodeAPI p uId id' = withAccess (Proxy :: Proxy (NodeAPI a)) Proxy uId (PathNode
:<|> catApi id'
:<|> searchDocs id'
:<|> Share.api id'
-- Pairing Tools
:<|> pairWith id'
:<|> pairs id'
......
{-|
Module : Gargantext.API.Node.Share
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Gargantext.API.Node.Share
where
import Data.Aeson
import Data.Swagger
import Data.Text (Text)
import GHC.Generics (Generic)
import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Action.Share (shareNodeWith)
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Prelude
import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..))
import Gargantext.Prelude
import Servant
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
------------------------------------------------------------------------
data ShareNode = ShareNode { username :: Text }
deriving (Generic)
------------------------------------------------------------------------
-- TODO unPrefix "pn_" FromJSON, ToJSON, ToSchema, adapt frontend.
instance FromJSON ShareNode
instance ToJSON ShareNode
instance ToSchema ShareNode
instance Arbitrary ShareNode where
arbitrary = elements [ ShareNode "user1"
, ShareNode "user2"
]
------------------------------------------------------------------------
-- TODO permission
api :: HasNodeError err
=> NodeId
-> ShareNode
-> Cmd err Int
api nId (ShareNode user) =
fromIntegral <$> shareNodeWith nId (UserName user)
------------------------------------------------------------------------
type API = Summary " Share Node with username"
:> ReqBody '[JSON] ShareNode
:> Post '[JSON] Int
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